[Haskell-cafe] order of arguments matters

2011-03-18 Thread Peter Padawitz
Why does only tr2 work, although the only difference between tr1 and  
tr2 is the order of arguments?


import Data.Tree (Tree(..))

data Type a where Tree:: Type a - Type (Tree a)
  Int :: Type Int
  String  :: Type String

type Traversal1 = forall a.a - Type a - a

type Traversal2 = forall a.Type a - a - a

tr1 :: Traversal1
tr1 (Node _ (t:_)) (Tree Int) = Node 1 [t]
tr1 n Int = n+n
tr1 s String  = s++s

tr2 :: Traversal2
tr2 (Tree Int) (Node _ (t:_)) = Node 1 [t]
tr2 Int n = n+n
tr2 String s  = s++s

Couldn't match expected type `a' against inferred type `Tree Int'
  `a' is a rigid type variable bound by
  the type signature for `tr1' at tratest.hs:9:25
In the pattern: Node _ (t : _)
In the definition of `tr1':
tr1 (Node _ (t : _)) (Tree Int) = Node 1 [t]


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


[Haskell-cafe] Set monad

2011-01-08 Thread Peter Padawitz

Hi,

is there any way to instantiate m in Monad m with a set datatype in  
order to implement the usual powerset monad?


My straightforward attempt failed because the bind operator of this  
instance requires the Eq constraint on the argument types of m.


Peter



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


[Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Peter Padawitz
A simplied version of Example 5-16 in Manna's classical book 
Mathematical Theory of Computation:


foo x = if x == 0 then 0 else foo (x-1)*foo (x+1)

If run with ghci, foo 5 does not terminate, i.e., Haskell does not look 
for all outermost redices in parallel. Why? For efficiency reasons?


It's a pity because a parallel-outermost strategy would be complete.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] monad constraint + record update

2008-12-22 Thread Peter Padawitz
I'd like to define a monad Set for types in the class Eq. But how can 
the arguments of Set be constrained when Set is defined as an instance 
of Monad? instance Eq a = Monad Set where ... obviously cannot work.


Is there a standard update function for fields in data types, something 
that OO programmers do with assignments like obj.attr := value ?


Peter

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



[Haskell-cafe] compilation question

2008-11-11 Thread Peter Padawitz

At first a type of arithmetic expressions and its generic evaluator:

data Expr = Con Int | Var String | Sum [Expr] | Prod [Expr] | Expr :- 
Expr |

   Int :* Expr | Expr :^ Int

data ExprAlg a = ExprAlg {con :: Int - a, var :: String - a, sum_ :: 
[a] - a,

 prod :: [a] - a, sub :: a - a - a,
 scal :: Int - a - a, expo :: a - Int - a}
   
eval :: ExprAlg a - Expr - a

eval alg (Con i)   = con alg i
eval alg (Var x)   = var alg x
eval alg (Sum es)  = sum_ alg (map (eval alg) es)
eval alg (Prod es) = prod alg (map (eval alg) es)
eval alg (e :- e') = sub alg (eval alg e) (eval alg e')
eval alg (n :* e)  = scal alg n (eval alg e)
eval alg (e :^ n)  = expo alg (eval alg e) n

Secondly, a procedural version of eval (in fact based on continuations):

data Id a = Id {out :: a} deriving Show

instance Monad Id where (=) m = ($ out m); return = Id

peval :: ExprAlg a - Expr - Id a
peval alg (Con i)   = return (con alg i)
peval alg (Var x)   = return (var alg x)
peval alg (Sum es)  = do as - mapM (peval alg) es; return (sum_ alg as)
peval alg (Prod es) = do as - mapM (peval alg) es; return (prod alg as)
peval alg (e :- e') = do a - peval alg e; b - peval alg e'; return 
(sub alg a b)

peval alg (n :* e)  = do a - peval alg e; return (scal alg n a)
peval alg (e :^ n)  = do a - peval alg e; return (expo alg a n)

My question: Is peval less time- or space-consuming than eval? Or would 
ghc, hugs et al. optimize eval towards peval by themselves?


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


[Haskell-cafe] lazy evaluation

2008-02-06 Thread Peter Padawitz
Can anybody give me a simple explanation why the second definition of a 
palindrome checker does not terminate, although the first one does?


pal :: Eq a = [a] - Bool
pal s = b where (b,r) = eqrev s r []

eqrev :: Eq a = [a] - [a] - [a] - (Bool,[a])
eqrev (x:s1) ~(y:s2) acc = (x==yb,r) where (b,r) = eqrev s1 s2 (x:acc)
eqrev _ _ acc  = (True,acc)

pal :: Eq a = [a] - Bool
pal s = b where (b,r) = eqrev' s r

eqrev' :: Eq a = [a] - [a] - (Bool,[a])
eqrev' (x:s1) ~(y:s2) = (x==yb,r++[y]) where (b,r) = eqrev' s1 s2
eqrev' _ _   = (True,[])

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


[Haskell-cafe] type classes

2007-12-14 Thread Peter Padawitz
I'd like to define several instances of the same type class with the 
same type variable instance. Only method instances differ. How can I do 
this without writing copies of the type class?


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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Try again without missing out the list...

Peter Padawitz wrote:
 Jules Bean wrote:
 Incidentally, I question why the compFoo are methods. Why not 
just make them polymorphic functions? They don't look like you expect 
instances to change them. The code continues to compile if I make them 
functions and amend their signatures as required.


 I put compFoo into the class for the same reason why /= is part of 
the class Eq: both functions are unique as soon as the others have 
been instantiated.


I believe you misunderstand the reason.

/= is part of Eq in case a particular instance has a particularly 
efficient way to implement /=, rather than using not and (==).


Being unique as soon as the others are implemented is not a reason 
not to make it a method.


It might not have been the reason, but it is a nice effect that is often 
taken advantage of.


What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the evaluation 
(compFoo) of Sig-terms in Sig-algebras.



compBlock :: (Java block command intE boolE) = Block - block
compBlock = block_ . map compCommand

still retains that property.


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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Peter Padawitz wrote:


Jules Bean wrote:


Peter Padawitz wrote:

What is so bad about making compFoo part of the class? It reduces 
the code (constraints can be avoided) and reflects the close 
connection between  a signature Sig (implemented by the class) and 
the evaluation (compFoo) of Sig-terms in Sig-algebras.


making it part of the class allows instances to override the 
implementation.


Which in this case is a strange thing to do.


Sure, but this can only happen because Haskell does not check whether 
the instances satisfy the equations in the class. The type class 
concept would be cleaner if all methods (partially or totally) 
defined by equations within the class were not allowed to be 
instantiated!



I don't see why!

In the class

class Foo a where
  f :: a - Int
  g :: b - Integer
  g = fromIntegral . f

The equations within the class are defaults, not equations. 


I must admit that I didn't know this... Nevertheless, won't you agree 
that the default and the actual instance should be semantically equivalent?



The equation for 'g' is a default, not a rule.

If you want equations, you do it outside the class. I have written 
that class wrongly, I should actually write g = fromIntegral . f as a 
function outside the class, thus guaranteeing the implementation and 
stopping people breaking that invariant.


The purpose of methods with defaults is to allow the possibility that 
there is an obvious natural way to implement one function in terms of 
others, but there might be more efficient ways.


For example, the Foldable class should (but doesn't) have a member 
length. This could be defaulted to length . toList, but have a more 
efficient implementation in Sequence, which stores its own length anyway.


Or maybe we are at cross-purposes.


No no, default functions make sense.

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


Re: [Haskell-cafe] Re: Re: type class question

2007-12-07 Thread Peter Padawitz
Functional dependencies don't work in my case. Actually, I don't see why 
they should.


What seems to be needed here is a type class construct with a kind of 
record parameter so that instance conflicts cannot occur.


Jules Bean wrote:


Ben Franksen wrote:


Ryan Ingram wrote:


On 12/5/07, Ben Franksen [EMAIL PROTECTED] wrote:
You would have to use functional dependencies or associated types to
eliminate this error.  Alternatively, you can add a dummy argument 
of type
block and pass undefined :: BlockType in to help choose the 
instance

declaration.



Sounds reasonable, and in fact that was what I tried first. However

data Command = Skip

class Java block command | command - block where
  block_ :: [command] - block

  compBlock :: [Command] - block
  compBlock = block_ . map compCommand

  compCommand :: Command - command

still gives

Could not deduce (Java block command1)
  from the context (Java block command)
  arising from use of `block_' at Bla.hs:7:14-19
Possible fix:
  add (Java block command1)
  to the class or instance method `compBlock'
In the first argument of `(.)', namely `block_'
In the expression: block_ . (map compCommand)
In the definition of `compBlock':
compBlock = block_ . (map compCommand)

which is /exactly/ the same error as I get w/o the fundep.



Yes, because command determines block but block doesn't determine 
command.


So in a usage of 'compBlock' it has no way of deciding which 'command' 
to use, although it can choose the block from the return type.


You could have command - block, block - command, if that is indeed 
true.


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




--
Prof. Dr. Peter Padawitz
Informatik 1
University of Dortmund  
D-44221 Dortmund
Germany 
phone   +49-231-755-5108

fax +49-231-755-6555
secretary   +49-231-755-6223
email   [EMAIL PROTECTED]
internethttp://funlog.padawitz.de

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


Re: [Haskell-cafe] Re: Re: type class question

2007-12-07 Thread Peter Padawitz

Jules Bean wrote:


Peter Padawitz wrote:


Jules Bean wrote:


Peter Padawitz wrote:

Functional dependencies don't work in my case. Actually, I don't 
see why they should.




Ah well, it's cruel to say that without explaining to us why!



Cause I don't see why the instantiation conflicts pointed out by 
others would vanish then.



They would.

If it's really true that there is only one possible choice of b,c,d 
for any particular a, then there are no conflicts, so you'd get no 
errors.


How can ghci know this even if no instance has been defined?


So the fundep would solve the problem.


But, actually, it doesn't :-(


class Java (a,b,c,d) where 



Yeah... but ghc accepts only type variables here, not arbitrary 
polymorphic types.



Indeed, but there is a workaround:

class Java all a b c d |
   all - a, all - b, all - c, all - d, a,b,c,d - all


Same problem.

If I omit the comp functions (see below), everything works. If I add 
them, all proposed solutions fail with error messages of the form


Could not deduce (Java block1 ) from the context (Java block ) 
arising from use of `prod' at ...


(see also Ben Franksen's comment from yesterday).

***

type Block   = [Command]
data Command = Skip | Assign String IntE | Cond BoolE Block Block | Loop 
BoolE Block
data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE] | Prod 
[IntE]

data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

class Java block command intE boolE
  where block_ :: [command] - block
skip :: command
assign :: String - intE - command
cond :: boolE - block - block - command
loop :: boolE - block - command
intE_ :: Int - intE
var :: String - intE
sub :: intE - intE - intE
sum_ :: [intE] - intE
prod :: [intE] - intE
boolE_ :: Bool - boolE
greater :: intE - intE - boolE
not_ :: boolE - boolE

compBlock :: Block - block

compBlock = block_ . map compCommand

compCommand :: Command - command

compCommand Skip   = skip
compCommand (Assign x e)   = assign x (compIntE e)
compCommand (Cond be cs cs') = cond (compBoolE be) (compBlock 
cs) (compBlock cs')

compCommand (Loop be cs)= loop (compBoolE be) (compBlock cs)

compIntE :: IntE - intE

compIntE (IntE i)   = intE_ i
compIntE (Var x)= var x
compIntE (Sub e e') = sub (compIntE e) (compIntE e')
compIntE (Sum es)   = sum_ (map compIntE es)
compIntE (Prod es)  = prod (map compIntE es)

compBoolE :: BoolE - boolE

compBoolE (BoolE b)  = boolE_ b
compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
compBoolE (Not be)   = not_ (compBoolE be)

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


Re: [Haskell-cafe] Re: Re: type class question

2007-12-07 Thread Peter Padawitz

Jules Bean wrote:


Peter Padawitz wrote:

Functional dependencies don't work in my case. Actually, I don't see 
why they should.



Ah well, it's cruel to say that without explaining to us why!


Cause I don't see why the instantiation conflicts pointed out by others 
would vanish then.


I'm not sure why a complete cyclic dep a - b - c - d - a isn't 
what you want.


What seems to be needed here is a type class construct with a kind of 
record parameter so that instance conflicts cannot occur.



I'm not entirely sure what you intend to mean by this, but if you mean 
what I guess you mean:


class Java (a,b,c,d) where 


Yeah... but ghc accepts only type variables here, not arbitrary 
polymorphic types.


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


Re: [Haskell-cafe] type class question

2007-12-06 Thread Peter Padawitz
Yes, the recursive calls of compCommand are supposed to be calls of 
compBlock.


The intention of the program is a generic evaluator comp... of 
Sigma-terms in arbitrary Sigma-algebras. The signature Sigma is given by 
the first 4 types (and the corresponding functions in the class 
declaration), the terms are the objects of the types, and the algebras 
are the class instances.


The problem with my implementation in terms of multiple-parameter 
classes seems to be - I conclude this from Ryan's comment - that  the 
intended dependency among the parameters is not reflected here. But what 
are the alternatives? Roughly said, I need a construct that allows me 
gather several type variables such that an instance is always an 
instance of all of them.




On Dec 3, 2007 7:43 AM, Peter Padawitz [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


What is wrong here? ghci tries (and fails) to deduce certain types
for the comp functions that I did not expect.

|type Block   = [Command]
data Command = Skip | Assign String IntE | Cond BoolE Block Block |
   Loop BoolE Block
data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE]
| Prod [IntE]
data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

class Java block command intE boolE
   where block_ :: [command] - block
 skip :: command
 assign :: String - intE - command
 cond :: boolE - block - block - command
 loop :: boolE - block - command
 intE_ :: Int - intE
 var :: String - intE
 sub :: intE - intE - intE
 sum_ :: [intE] - intE
 prod :: [intE] - intE
 boolE_ :: Bool - boolE
 greater :: intE - intE - boolE
 not_ :: boolE - boolE

 compBlock :: Block - block
 compBlock = block_ . map compCommand

 compCommand :: Command - command
 compCommand Skip   = skip
 compCommand (Assign x e)   = assign x (compIntE e)
 compCommand (Cond be c c') = cond (compBoolE be)
(compCommand c)
 
(compCommand c')

 compCommand (Loop be c)= loop (compBoolE be)
(compCommand c)-}

 compIntE :: IntE - intE
 compIntE (IntE i)   = intE_ i
 compIntE (Var x)= var x
 compIntE (Sub e e') = sub (compIntE e) (compIntE e')
 compIntE (Sum es)   = sum_ (map compIntE es)
 compIntE (Prod es)  = prod (map compIntE es)
 
 compBoolE :: BoolE - boolE

 compBoolE (BoolE b)  = boolE_ b
 compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
 compBoolE (Not be)   = not_ (compBoolE be)
|


Well, first of all, the definition of compCommand should use calls to 
compBlock, not recursive calls to compCommand.  But that's not the 
main source of your problems.


What exactly are you trying to accomplish?  And why do you need a type 
class?


-Brent


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


[Haskell-cafe] type class question

2007-12-03 Thread Peter Padawitz
What is wrong here? ghci tries (and fails) to deduce certain types for 
the comp functions that I did not expect.


|type Block   = [Command]
data Command = Skip | Assign String IntE | Cond BoolE Block Block |
  Loop BoolE Block
data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE] | Prod 
[IntE]

data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

class Java block command intE boolE
  where block_ :: [command] - block
skip :: command
assign :: String - intE - command
cond :: boolE - block - block - command
loop :: boolE - block - command
intE_ :: Int - intE
var :: String - intE
sub :: intE - intE - intE
sum_ :: [intE] - intE
prod :: [intE] - intE
boolE_ :: Bool - boolE
greater :: intE - intE - boolE
not_ :: boolE - boolE

compBlock :: Block - block
compBlock = block_ . map compCommand

compCommand :: Command - command
compCommand Skip   = skip
compCommand (Assign x e)   = assign x (compIntE e)
compCommand (Cond be c c') = cond (compBoolE be) (compCommand c)
 (compCommand c')
compCommand (Loop be c)= loop (compBoolE be) (compCommand c)-}

compIntE :: IntE - intE
compIntE (IntE i)   = intE_ i
compIntE (Var x)= var x
compIntE (Sub e e') = sub (compIntE e) (compIntE e')
compIntE (Sum es)   = sum_ (map compIntE es)
compIntE (Prod es)  = prod (map compIntE es)

compBoolE :: BoolE - boolE

compBoolE (BoolE b)  = boolE_ b
compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
compBoolE (Not be)   = not_ (compBoolE be)
|
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Graphics.SOE

2007-09-21 Thread Peter Padawitz

Can scrollbars be attached to windows created with openWindow?

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


[Haskell-cafe] lazy patterns versus where-clauses

2007-06-21 Thread Peter Padawitz

Is f(~p(x))=e(x) semantically equivalent to: f(z)=e(x) where p(x)=z?

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


[Haskell-cafe] Haskell - Tk

2007-01-22 Thread Peter Padawitz
Does anybody know O'Haskell or Timber and its interface Tk.hs to Tcl/Tk 
(see here http://fldit-www.cs.uni-dortmund.de/%7Epeter/tk.html)?


I have the following problem:

Tk.hs http://fldit-www.cs.uni-dortmund.de/%7Epeter/Tk.hs contains a 
record (structure) /Canvas/ with selectors


line  :: [(Int,Int)]  - [LineOpt]  - Request Line
polygon   :: [(Int,Int)]  - [PolygonOpt]   - Request Polygon

that are compiled into synonymous Tk widgets for lines and polygons, respectively. Unfortunately, Tk.hs crashes if the point list parameter of line or polygon 
contains more than 100 points. Why??? 

Of course, one may split a point list into smaller ones that are compiled correctly. But this may not produce the same picture, for instance, if the entire list 
represents a polygon to be filled or a line to be smoothened.


Peter


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


[Haskell-cafe] HGL documentation

2005-05-02 Thread Peter Padawitz
Is there a HGL documentation in one volume (e.g. pdf file)? Printing all 
pieces of http://www.haskell.org/ghc/docs/latest/html/libraries/HGL is a 
little tedious...

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


Monad constructors

2003-07-11 Thread Peter Padawitz
Why must every Monad instance be a datatype or newtype, even if there 
will be just a single constructor?

Peter

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


constructors in O'Haskell

2003-07-11 Thread Peter Padawitz
How may I hide constructors in O'Haskell 'cause export lists don't work 
in this language?

Peter

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Expander2

2002-10-08 Thread Prof. Dr. Peter Padawitz

Expander2: A Formal Methods Presenter and Animator
==

Expander2 has been designed as a multi-purpose workbench for interactive
logical inference, constraint solving, data flow analysis and other
procedures building up proofs or computation sequences. Moreover,
several interpreters translate expressions into tailor-made
two-dimensional representations that range from trees and term graphs to
tables, fractals or other turtle-system-generated pictures.

Expander2 has been implemented in O'Haskell}, an extension of
Haskell with object-oriented features for reactive programming and a
typed interface to Tcl/Tk for developing GUIs. Besides a comfortable GUI
the design goals of Expander2 were to integrate testing, proving and
visualizing deductive methods, to admit several degrees of interaction
and to keep the system open for extensions or adaptations of individual
components to changing demands.

Proofs and computations performed with Expander2 follow the rules and
the semantics of swinging types
(ls5-www.cs.uni-dortmund.de/~peter/Swinging.html). 
Swinging types combine constructor-based visible types with state-based
hidden types and have unique (Herbrand) models, which interpret
relations as the least or greatest solutions of their axioms.

All features of the system and their use are described in the manual

ls5-www.cs.uni-dortmund.de/~peter/Expander2/Expander2.html 

(sorry, this is still a big file, it will be splitted soon; PostScript
version: ../Expander2/Expander2.ps.gz). The paper
../Expander2/Chiemsee.ps.gz concentrates on the prover features.
Download everything with ../Expander2.tar.gz.

Please email comments, bugs, etc. to [EMAIL PROTECTED]

Peter
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe