Re: [Haskell-cafe] Semantic Domain, Function, and denotational model.....

2008-09-16 Thread Daryoush Mehrtash
ّ I don't follow the at and  type B a.  Behavior a itself is a
time function.   At least in the version of the code that was
developed in Pual Hudak's Haskell School of Expression it was defined
as:

 newtype Behavior a
   = Behavior (([Maybe UserAction],[Time]) - [a])

In a function like time you can see that the at function makes things simpler.

In the original version  time was defined as:

 time :: Behavior Time
 time = Behavior (\(_,ts) - ts)

In Conal's paper

time :: Behavior Time
at time = id

Comparing the two implementation of the time, it seems to me that at
and type B a has put the design on a more solid ground.  But I don't
quite understand the thought process, or the principal behind what is
happening.

daryoush


On Mon, Sep 15, 2008 at 10:46 AM, Ryan Ingram [EMAIL PROTECTED] wrote:
 Here's a quick overview that might help you.

 For a reactive behavior, we have two types to think about:

 type B a = Time - a
(the semantic domain)

 data Behavior a = ?
(the library's implementation).
 at :: Behavior a - B a
(observation function)

 This is really just classic information hiding as you would do with
 any abstract data type.  Consider a simple stack data structure that
 supports push and pop.

 data S a = S
 { popS :: Maybe (a, S a)
 , pushS :: a - S a
 }

 data Stack a = ?
 observeStack :: Stack a - S a

 As a library user, you don't really care about the implementation of
 Stack, just as a user of Conal's library doesn't really care about the
 implementation of Behavior.  What you *do* care about is that you can
 think about it in the simpler terms of Time - a which is the model
 he has chosen.

 The rest of the library design comes from taking that model and
 thinking about what typeclasses and operations Time - a should
 support, and creating typeclass morphisms between Behavior a and B a
 where necessary.  For example:

 -- This makes (r - a) into a functor over a; it is a generalization of Time 
 - a
 instance Functor ((-) r) where
-- fmap :: (a - b) - (r - a) - (r - b)
fmap f x = \r - f (x r)
-- or, fmap = (.), if you're golfing :)

 In order for the morphism between B and Behavior to make sense, you
 want this law to hold:
   fmap f (at behavior) = at (fmap f behavior)
 for all behavior :: Behavior a.

 The fmap on the left applies to B which is (Time -); the fmap on the
 right applies to Behavior.

 Conal writes this law more elegantly like this:
 instance(semantic) Functor Behavior where
fmap f . at = at . fmap f

 As long as you as the user can think about behaviors generally as
 functions of Time, you can ignore the implementation details, and
 things that you expect to work should work.  This drives the design of
 the entire library, with similar morphisms over many typeclasses
 between Event and E, Reactive and B, etc.

  -- ryan

 On Mon, Sep 15, 2008 at 10:13 AM, Daryoush Mehrtash [EMAIL PROTECTED] wrote:
 Interestingly, I was trying to read his paper when I realized that I
 needed to figure out the meaning of denotational model, semantic
 domain, semantic functions.  Other Haskell books didn't talk about
 design in those terms, but obviously for him this is how he is driving
 his design.   I am looking for a simpler tutorial, text book like
 reference on the topic.

 Daryoush

 On Mon, Sep 15, 2008 at 1:33 AM, Ryan Ingram [EMAIL PROTECTED] wrote:
 I recommend reading Conal Elliott's Efficient Functional Reactivity
 paper for an in-depth real-world example.

 http://www.conal.net/papers/simply-reactive

  -- ryan

 On Sun, Sep 14, 2008 at 11:31 AM, Daryoush Mehrtash [EMAIL PROTECTED] 
 wrote:
 I have been told that for a Haskell/Functional programmer the process
 of design starts with defining Semantic Domain, Function, and
 denotational model of the problem.  I have done some googling on the
 topic but haven't found a good reference on it.I would appreciate
 any good references on the topic.

 thanks,

 daryoush

 ps.  I have found referneces like
 http://en.wikibooks.org/wiki/Haskell/Denotational_semantics  which
 talks about semantic domain for the Haskell programs 10, 9+1, 2*5
 which doesn't do any good for me.I need something with a more real
 examples.
 ___
 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] Re: Comparing GADTs for Eq and Ord

2008-09-16 Thread apfelmus
Tom Hawkins wrote:
 apfelmus wrote:
 So, in other words, in order to test whether terms constructed with  Equal  
 are
 equal, you have to compare two terms of different type for equality. Well,
 nothing easier than that:

(===) :: Expr a - Expr b - Bool
Const   === Const = True
(Equal a b) === (Equal a' b') = a === a'  b === b'
_   === _ = False

instance Eq (Expr a) where
(==) = (===)
 
 OK.  But let's modify Expr so that Const carries values of different types:
 
 data Expr :: * - * where
   Const :: a - Term a
   Equal :: Term a - Term a - Term Bool
 
 How would you then define:
 
 Const a === Const b  = ...
 

Well,

Const :: a - Term a

is too general anyway, you do need some information on  a  to be able to compare
different  Const  terms. An  Eq  constraint on  a  is the minimum:

Const :: Eq a = a - Term a

But that's not enough for  (===)  of course, additional information as suggested
by others is needed.


Regards,
apfelmus

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


Re: [Haskell-cafe] Semantic Domain, Function, and denotational model.....

2008-09-16 Thread Ryan Ingram
The key insight is that Behavior a is not necessarily a time function;
it's abstract.  But you can treat it as if it was one by observing it
with at.

In Conal's paper, the internal type of behavior is:

 -- composition of types; like (.) at the type level
 newtype O h g a = O (h (g a))

 -- function type that can directly observe some constant functions
 data Fun t a = K a | Fun (t - a)

 -- Behavior a ~~ Reactive (Fun Time a)
 type Behavior = Reactive `O` Fun Time

 -- Reactive has a current value and an event stream of values to switch to at 
 particular times
 -- Then an event is just a reactive that might not have a current value until 
 some time in the future.
 data Reactive a = Stepper a (Event a)
 newtype Event a = Ev (Future (Reactive a))

Now, at the internal level, you can write the primitive time as

 time :: Behavior Time
 time = O (pure (Fun id))

with pure from the Applicative instance for Reactive:

 pure x = Stepper x never

never is a future that never occurs, so the reactive value never changes.

From a users' point of view, all this is invisible--you only get a few
observation functions (including at).  Internally, however, constant
behaviors, or behaviors that contain steps that are constant, can be
evaluated extremely quickly; once the behavior returns K x, you know
that the result can't change until the next event in the reactive
stream.  You only need to continuously evaluate the behavior if you
get a Fun result.  See sinkB on page 9 of the paper to understand
how this is used to improve performance.

The semantic function at drives the model; it allows you to describe
the laws for the library to fulfill very succinctly:

at (fmap f x) = fmap f (at x)
at (pure x) = pure x
at (f * x) = at f * at x
at (return x) = return x
at (m = f) = at m = at . f
etc.

Similarily, for Futures, we have force :: Future a - (Time, a)

force (fmap f z) = (t, f x) where (t,x) = force z
force (pure x) = (minBound, x)
force (ff * fx) = (max tf tx, f x) where (tf, f) = force ff ; (tx,
x) = force fx
force (return x) = (minBound, x)
force (m = f) = (max tm tx, x) where (tm, v) = force m; (tx, x) = force (f v)
etc.

This gives the library user solid ground to stand on when reasoning
about their code; it should do what they expect.  And it gives the
library author a very strong goal to shoot for: just fulfill these
laws, and the code is correct!  This allows radical redesigns of the
internals of the system while maintaining a consistent and intuitive
interface that reuses several classes that the user is hopefully
already familiar with: monoids, functors, applicative functors, and
monads.

  -- ryan

2008/9/16 Daryoush Mehrtash [EMAIL PROTECTED]:
 ّ I don't follow the at and  type B a.  Behavior a itself is a
 time function.   At least in the version of the code that was
 developed in Pual Hudak's Haskell School of Expression it was defined
 as:

 newtype Behavior a
   = Behavior (([Maybe UserAction],[Time]) - [a])

 In a function like time you can see that the at function makes things 
 simpler.

 In the original version  time was defined as:

 time :: Behavior Time
 time = Behavior (\(_,ts) - ts)

 In Conal's paper

 time :: Behavior Time
 at time = id

 Comparing the two implementation of the time, it seems to me that at
 and type B a has put the design on a more solid ground.  But I don't
 quite understand the thought process, or the principal behind what is
 happening.

 daryoush


 On Mon, Sep 15, 2008 at 10:46 AM, Ryan Ingram [EMAIL PROTECTED] wrote:
 Here's a quick overview that might help you.

 For a reactive behavior, we have two types to think about:

 type B a = Time - a
(the semantic domain)

 data Behavior a = ?
(the library's implementation).
 at :: Behavior a - B a
(observation function)

 This is really just classic information hiding as you would do with
 any abstract data type.  Consider a simple stack data structure that
 supports push and pop.

 data S a = S
 { popS :: Maybe (a, S a)
 , pushS :: a - S a
 }

 data Stack a = ?
 observeStack :: Stack a - S a

 As a library user, you don't really care about the implementation of
 Stack, just as a user of Conal's library doesn't really care about the
 implementation of Behavior.  What you *do* care about is that you can
 think about it in the simpler terms of Time - a which is the model
 he has chosen.

 The rest of the library design comes from taking that model and
 thinking about what typeclasses and operations Time - a should
 support, and creating typeclass morphisms between Behavior a and B a
 where necessary.  For example:

 -- This makes (r - a) into a functor over a; it is a generalization of 
 Time - a
 instance Functor ((-) r) where
-- fmap :: (a - b) - (r - a) - (r - b)
fmap f x = \r - f (x r)
-- or, fmap = (.), if you're golfing :)

 In order for the morphism between B and Behavior to make sense, you
 want this law to hold:
   fmap f (at behavior) = at (fmap f behavior)
 for all behavior :: 

[Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Mauricio

Hi,

A small annoyance some users outside
english speaking countries usually
experiment when learning programming
languages is that real numbers use
a '.' instead of ','. Of course, that
is not such a problem except for the
inconsistence between computer and
free hand notation.

Do you think 'read' (actually,
'readsPrec'?) could be made to also
read the international convention
(ie., read 1,5 would also work
besides read 1.5)? I'm happy to
finaly use a language where I can
use words of my language to name
variables, so I wonder if we could
also make that step.

Thanks,
Maurício

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


Re: [Haskell-cafe] Re: Import qualified, inverse of hiding

2008-09-16 Thread John Van Enk
I've dropped it on the discuss page:
http://www.haskell.org/haskellwiki/Talk:Import
Perhaps others have some input before I stick it on the page.

On Mon, Sep 15, 2008 at 4:36 PM, Paulo Tanimoto [EMAIL PROTECTED]wrote:

 On Mon, Sep 15, 2008 at 3:04 PM, John Van Enk [EMAIL PROTECTED] wrote:
  Would it make sense to add multiple imports to that wiki page? I'm not
 sure
  if this is supported outside of GHC, but I've found it useful.
   1 module Main where
   2
   3 import qualified Prelude as P
   4 import Prelude ((++),show,($))
   5
   6 main = P.putStrLn (show $ P.length $ show $ [1] ++ [2,3])
 

 I don't know if that's exclusive to GHC, but I think it would be nice
 to have your example on the Wiki -- perhaps at the bottom.  We could
 put it under discussion, if we're not sure.

 Thanks,

 Paulo




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


Re: [Haskell-cafe] Semantic Domain, Function, and denotational model.....

2008-09-16 Thread Conal Elliott
Hi Ryan,

Thanks very much for these explanations.  Clear and right on!

Best regards,  - Conal

P.S. I'll be at ICFP and am looking forward to seeing folks there.

2008/9/16 Ryan Ingram [EMAIL PROTECTED]

 The key insight is that Behavior a is not necessarily a time function;
 it's abstract.  But you can treat it as if it was one by observing it
 with at.

 In Conal's paper, the internal type of behavior is:

  -- composition of types; like (.) at the type level
  newtype O h g a = O (h (g a))

  -- function type that can directly observe some constant functions
  data Fun t a = K a | Fun (t - a)

  -- Behavior a ~~ Reactive (Fun Time a)
  type Behavior = Reactive `O` Fun Time

  -- Reactive has a current value and an event stream of values to switch
 to at particular times
  -- Then an event is just a reactive that might not have a current value
 until some time in the future.
  data Reactive a = Stepper a (Event a)
  newtype Event a = Ev (Future (Reactive a))

 Now, at the internal level, you can write the primitive time as

  time :: Behavior Time
  time = O (pure (Fun id))

 with pure from the Applicative instance for Reactive:

  pure x = Stepper x never

 never is a future that never occurs, so the reactive value never changes.

 From a users' point of view, all this is invisible--you only get a few
 observation functions (including at).  Internally, however, constant
 behaviors, or behaviors that contain steps that are constant, can be
 evaluated extremely quickly; once the behavior returns K x, you know
 that the result can't change until the next event in the reactive
 stream.  You only need to continuously evaluate the behavior if you
 get a Fun result.  See sinkB on page 9 of the paper to understand
 how this is used to improve performance.

 The semantic function at drives the model; it allows you to describe
 the laws for the library to fulfill very succinctly:

 at (fmap f x) = fmap f (at x)
 at (pure x) = pure x
 at (f * x) = at f * at x
 at (return x) = return x
 at (m = f) = at m = at . f
 etc.

 Similarily, for Futures, we have force :: Future a - (Time, a)

 force (fmap f z) = (t, f x) where (t,x) = force z
 force (pure x) = (minBound, x)
 force (ff * fx) = (max tf tx, f x) where (tf, f) = force ff ; (tx,
 x) = force fx
 force (return x) = (minBound, x)
 force (m = f) = (max tm tx, x) where (tm, v) = force m; (tx, x) = force
 (f v)
 etc.

 This gives the library user solid ground to stand on when reasoning
 about their code; it should do what they expect.  And it gives the
 library author a very strong goal to shoot for: just fulfill these
 laws, and the code is correct!  This allows radical redesigns of the
 internals of the system while maintaining a consistent and intuitive
 interface that reuses several classes that the user is hopefully
 already familiar with: monoids, functors, applicative functors, and
 monads.

  -- ryan

 2008/9/16 Daryoush Mehrtash [EMAIL PROTECTED]:
  ّ I don't follow the at and  type B a.  Behavior a itself is a
  time function.   At least in the version of the code that was
  developed in Pual Hudak's Haskell School of Expression it was defined
  as:
 
  newtype Behavior a
= Behavior (([Maybe UserAction],[Time]) - [a])
 
  In a function like time you can see that the at function makes things
 simpler.
 
  In the original version  time was defined as:
 
  time :: Behavior Time
  time = Behavior (\(_,ts) - ts)
 
  In Conal's paper
 
  time :: Behavior Time
  at time = id
 
  Comparing the two implementation of the time, it seems to me that at
  and type B a has put the design on a more solid ground.  But I don't
  quite understand the thought process, or the principal behind what is
  happening.
 
  daryoush
 
 
  On Mon, Sep 15, 2008 at 10:46 AM, Ryan Ingram [EMAIL PROTECTED]
 wrote:
  Here's a quick overview that might help you.
 
  For a reactive behavior, we have two types to think about:
 
  type B a = Time - a
 (the semantic domain)
 
  data Behavior a = ?
 (the library's implementation).
  at :: Behavior a - B a
 (observation function)
 
  This is really just classic information hiding as you would do with
  any abstract data type.  Consider a simple stack data structure that
  supports push and pop.
 
  data S a = S
  { popS :: Maybe (a, S a)
  , pushS :: a - S a
  }
 
  data Stack a = ?
  observeStack :: Stack a - S a
 
  As a library user, you don't really care about the implementation of
  Stack, just as a user of Conal's library doesn't really care about the
  implementation of Behavior.  What you *do* care about is that you can
  think about it in the simpler terms of Time - a which is the model
  he has chosen.
 
  The rest of the library design comes from taking that model and
  thinking about what typeclasses and operations Time - a should
  support, and creating typeclass morphisms between Behavior a and B a
  where necessary.  For example:
 
  -- This makes (r - a) into a functor over a; it is a generalization of

[Haskell-cafe] How to check if two Haskell files are the same?

2008-09-16 Thread Mauricio

Hi,

I would like to write a Haskell pretty-printer,
using standard libraries for that. How can I
check if the original and the pretty-printed
versions are the same? For instance, is there
a file generated by GHC at the compilation
pipe that is always guaranteed to have the
same MD5 hash when it comes from equivalent
source?

Thanks,
Maurício

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


[Haskell-cafe] Problem with hscurses

2008-09-16 Thread david48
the getCh funtion is supposed to return an interpreted Key with values
like KeyChar c, KeyReturn, KeyBackspace, etc.

but in fact, it only ever returns KeyChar c values !

am I doing anything wrong ?

Here's an example program :

module Main where

import UI.HSCurses.Curses
import Text.Printf
import System.IO

main = do
  hSetBuffering stdout NoBuffering
  withCurses test1

withCurses f = do
  initScr
  echo False
  cBreak True
  res - f
  endWin
  return res

test1 = do
  c - getCh
  printf Touche : %s\r\n (show c)
  test1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2008-09-16 Thread Simon Peyton-Jones
The message below is a rather old thread but, as Ian says, it's related to

http://hackage.haskell.org/trac/ghc/ticket/1470
http://hackage.haskell.org/trac/ghc/ticket/1735

which I have been looking it in preparation for 6.10.

The good news is that I think I have fixed #1470.  I think #1735 is deeply 
dodgy code which is rendered unnecessary by #1470.

The key part is this (the full message is below):

| The Data instance that Derive generates is as follows:
|
|   instance (Data ctx a,
| Data ctx (BinTree a),
| Sat (ctx (BinTree a))) =
| Data ctx (BinTree a) where
|
| Note the recursive |Data ctx (BinTree a)| in the context. If I get
| rid of it (a correct manual instance is also included in the
| attachment) the example works.

This is indeed a Bad Instance. It says if you supply me with a (Data ctx 
(BinTree a)) dictionary, I will construct a (Data ctx (BinTree a)) dictionary. 
 It's akin to saying
instance Eq [a] = Eq [a]

Admittedly,
 a) #1470 meant that leaving off this constraint stopped the program compiling
 b) under very special conditions (I'm not quite sure what) you could
just about make such a program work (see #1735) with the Bad Instance

But the right thing is
  a) to fix #1470 (which I have done) and
  b) to omit the bad constraint from the instance declaration
(which needs a change to some library)

OK?  I'll commit the fix tomorrow.

Simon


| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of
| Alexey Rodriguez Yakushev
| Sent: 31 March 2008 14:47
| To: haskell-cafe
| Cc: [EMAIL PROTECTED]; Ralf Laemmel
| Subject: [Haskell-cafe] SYB with class: Bug in Derive.hs module
|
| Hi people (and Ralf and Alex),
|
| I found a bug in the SYB with class library when trying to implement
| generic equality. I am hoping that someone in the Cafe (maybe Ralf)
| can confirm it is a bug, or maybe show me that I am doing something
| wrong.
|
| I am using the Scrap your boilerplate with class library (http://
| homepages.cwi.nl/~ralf/syb3/). More precisely, I am using the library
| distributed by the HAppS project, because it works with GHC 6.8 . You
| can get the repository as follows:
|
| darcs get http://happs.org/HAppS/syb-with-class
|
| However, the offending module (Derive.hs) produces broken instances
| in both distributions.
|
| The bug:
| --
|
| Generic equality needs type safe casting when implemented in SYB3, I
| have tried both the gzipwith variant and using Pack datatypes
| (geq*.hs in the first distribution). However, both functions loop
| when applied to a tree value.
|
| This loop occurs when the functions try to cast one of the arguments.
| I have managed to reduce the error to a smaller source file that I
| send attached. It does the following:
|
|   main = print typeReps
|  
|   tree = (Bin (Leaf 1) (Leaf 2))::BinTree Int
|  
|   data Pack = forall x. Typeable x = Pack x
|  
|   packedChildren = gmapQ geqCtx Pack tree
|  
|   typeOfPack (Pack x) = typeOf x
|  
|   typeReps = map typeOfPack packedChildren
|
| Basically the tree is transformed into a list of Pack-ed values and
| then to a list of type representations. This program loops at
| typeOf when you call main.
|
| The Data instance that Derive generates is as follows:
|
|   instance (Data ctx a,
| Data ctx (BinTree a),
| Sat (ctx (BinTree a))) =
| Data ctx (BinTree a) where
|
| Note the recursive |Data ctx (BinTree a)| in the context. If I get
| rid of it (a correct manual instance is also included in the
| attachment) the example works.
|
| I thought of removing this from the context in the Derive source. But
| maybe I might break some other use cases. So I am asking for help!
| Should Derive be fixed? How?
|
| Cheers,
|
| Alexey

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


[Haskell-cafe] GHC trouble on Leopard

2008-09-16 Thread Miguel Vilaca

Hi,

I tried to compile some code on Mac Os X (Intel) Leopard.
I have GHC 6.8.3 installed - the installer from GHC webpage (GHC-6.8.3- 
i386.pkg).


But when I run make I get this error

ghc-6.8.3: could not execute: /Library/Frameworks/GHC.framework/ 
Versions/608/usr/lib/ghc-6.8.3/ghc-asm


The work-around of removing the option -fvia-C pointed somewhere on  
the web is not an option here due to library dependecies.


Any hints on how to solve this?

Thanks in advance

Miguel Vilaça

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


Hyena Status? Re: [Haskell-cafe] Starting Haskell with a web application

2008-09-16 Thread Donnie Jones
Hello Johan Tibell,

Hyena looks very interesting.  From the github tracking, you've been
working...  Maybe a release soon?

Also, I saw your slides from the 'Left-fold enumerators' presentation at
Galois.  Maybe include the slides in the docs/ for a release?

Thank you.
__
Donnie

On Thu, Mar 6, 2008 at 7:40 AM, Johan Tibell [EMAIL PROTECTED] wrote:

   Do you (both) have repos that I could download from? I quite interested
   in both projects, esp. the WSGI clone.

 Yes and no. The code [1] is in my darcs repository but is in an
 unusable state until I've fixed my incremental parser (in
 Hyena/Parser.hs) which I plan to do next week. I would like the first
 release to be nice and polished so I'm trying to not release anything
 prematurely.

 1. http://darcs.johantibell.com/hyena/
 ___
 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] Semantic Domain, Function, and denotational model.....

2008-09-16 Thread Daryoush Mehrtash
I can sort of see what is happening in time = O (pure (Fun id)).
But I am not sure I understand this:

time :: Behavior Time
at time = id

as I understand it at is a function that take Behaviour and returns
a function that is Time - a.How can you have a function on the
left side of the equation?

thanks,

Daryoush


2008/9/16 Conal Elliott [EMAIL PROTECTED]:
 Hi Ryan,

 Thanks very much for these explanations.  Clear and right on!

 Best regards,  - Conal

 P.S. I'll be at ICFP and am looking forward to seeing folks there.

 2008/9/16 Ryan Ingram [EMAIL PROTECTED]

 The key insight is that Behavior a is not necessarily a time function;
 it's abstract.  But you can treat it as if it was one by observing it
 with at.

 In Conal's paper, the internal type of behavior is:

  -- composition of types; like (.) at the type level
  newtype O h g a = O (h (g a))

  -- function type that can directly observe some constant functions
  data Fun t a = K a | Fun (t - a)

  -- Behavior a ~~ Reactive (Fun Time a)
  type Behavior = Reactive `O` Fun Time

  -- Reactive has a current value and an event stream of values to switch
  to at particular times
  -- Then an event is just a reactive that might not have a current value
  until some time in the future.
  data Reactive a = Stepper a (Event a)
  newtype Event a = Ev (Future (Reactive a))

 Now, at the internal level, you can write the primitive time as

  time :: Behavior Time
  time = O (pure (Fun id))

 with pure from the Applicative instance for Reactive:

  pure x = Stepper x never

 never is a future that never occurs, so the reactive value never
 changes.

 From a users' point of view, all this is invisible--you only get a few
 observation functions (including at).  Internally, however, constant
 behaviors, or behaviors that contain steps that are constant, can be
 evaluated extremely quickly; once the behavior returns K x, you know
 that the result can't change until the next event in the reactive
 stream.  You only need to continuously evaluate the behavior if you
 get a Fun result.  See sinkB on page 9 of the paper to understand
 how this is used to improve performance.

 The semantic function at drives the model; it allows you to describe
 the laws for the library to fulfill very succinctly:

 at (fmap f x) = fmap f (at x)
 at (pure x) = pure x
 at (f * x) = at f * at x
 at (return x) = return x
 at (m = f) = at m = at . f
 etc.

 Similarily, for Futures, we have force :: Future a - (Time, a)

 force (fmap f z) = (t, f x) where (t,x) = force z
 force (pure x) = (minBound, x)
 force (ff * fx) = (max tf tx, f x) where (tf, f) = force ff ; (tx,
 x) = force fx
 force (return x) = (minBound, x)
 force (m = f) = (max tm tx, x) where (tm, v) = force m; (tx, x) = force
 (f v)
 etc.

 This gives the library user solid ground to stand on when reasoning
 about their code; it should do what they expect.  And it gives the
 library author a very strong goal to shoot for: just fulfill these
 laws, and the code is correct!  This allows radical redesigns of the
 internals of the system while maintaining a consistent and intuitive
 interface that reuses several classes that the user is hopefully
 already familiar with: monoids, functors, applicative functors, and
 monads.

  -- ryan

 2008/9/16 Daryoush Mehrtash [EMAIL PROTECTED]:
  ّ I don't follow the at and  type B a.  Behavior a itself is a
  time function.   At least in the version of the code that was
  developed in Pual Hudak's Haskell School of Expression it was defined
  as:
 
  newtype Behavior a
= Behavior (([Maybe UserAction],[Time]) - [a])
 
  In a function like time you can see that the at function makes things
  simpler.
 
  In the original version  time was defined as:
 
  time :: Behavior Time
  time = Behavior (\(_,ts) - ts)
 
  In Conal's paper
 
  time :: Behavior Time
  at time = id
 
  Comparing the two implementation of the time, it seems to me that at
  and type B a has put the design on a more solid ground.  But I don't
  quite understand the thought process, or the principal behind what is
  happening.
 
  daryoush
 
 
  On Mon, Sep 15, 2008 at 10:46 AM, Ryan Ingram [EMAIL PROTECTED]
  wrote:
  Here's a quick overview that might help you.
 
  For a reactive behavior, we have two types to think about:
 
  type B a = Time - a
 (the semantic domain)
 
  data Behavior a = ?
 (the library's implementation).
  at :: Behavior a - B a
 (observation function)
 
  This is really just classic information hiding as you would do with
  any abstract data type.  Consider a simple stack data structure that
  supports push and pop.
 
  data S a = S
  { popS :: Maybe (a, S a)
  , pushS :: a - S a
  }
 
  data Stack a = ?
  observeStack :: Stack a - S a
 
  As a library user, you don't really care about the implementation of
  Stack, just as a user of Conal's library doesn't really care about the
  implementation of Behavior.  What you *do* care about is that you can
  think about 

Re: [Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Rafael C. de Almeida
Mauricio wrote:
 Hi,
 
 A small annoyance some users outside
 english speaking countries usually
 experiment when learning programming
 languages is that real numbers use
 a '.' instead of ','. Of course, that
 is not such a problem except for the
 inconsistence between computer and
 free hand notation.
 
 Do you think 'read' (actually,
 'readsPrec'?) could be made to also
 read the international convention
 (ie., read 1,5 would also work
 besides read 1.5)? I'm happy to
 finaly use a language where I can
 use words of my language to name
 variables, so I wonder if we could
 also make that step.
 

Isn't it locale dependent? If it isn't, it should be. Try setting your
locale right and see if things work. At least awk work fine that way.

Although I don't like too much that kinda stuff, I usually set the
locale to C so I keep all my programs behaving consistently. I have
problems with that stuff before (a file generated by an awk script had ,
instead of . and that would confuse other computers with a different
locale).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Tilo Wiklund
Wouldn't that make it hard to parse lists of floats?

On Tue, 2008-09-16 at 09:29 -0300, Mauricio wrote:
 Hi,
 
 A small annoyance some users outside
 english speaking countries usually
 experiment when learning programming
 languages is that real numbers use
 a '.' instead of ','. Of course, that
 is not such a problem except for the
 inconsistence between computer and
 free hand notation.
 
 Do you think 'read' (actually,
 'readsPrec'?) could be made to also
 read the international convention
 (ie., read 1,5 would also work
 besides read 1.5)? I'm happy to
 finaly use a language where I can
 use words of my language to name
 variables, so I wonder if we could
 also make that step.
 
 Thanks,
 Maurício
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Miguel Mitrofanov


On 16 Sep 2008, at 16:29, Mauricio wrote:


I'm happy to
finaly use a language where I can
use words of my language to name
variables, so I wonder if we could
also make that step.


Really?

There is a bunch of languages (like Glagol) that use words of  
Russian language as keywords; AFAIK there aren't any Russian  
programmer who uses them. I've always felt sorry for English-speaking  
programmers: they HAVE to use the same words as keywords and as usual  
talking words at the same time.

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


Re: [Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Twan van Laarhoven

Mauricio wrote:

Do you think 'read' (actually,
'readsPrec'?) could be made to also
read the international convention
(ie., read 1,5 would also work
besides read 1.5)? I'm happy to
finaly use a language where I can
use words of my language to name
variables, so I wonder if we could
also make that step.


That would be quite problematic in combination with lists, is

  read [1,2,3,4] == [1,2,3,4]

or

  read [1,2,3,4] == [1.2, 3.4]

Or something else?


Localized reading should be somewhere else, perhaps related to Locales.

As an aside, this is one of the (many) places where Haskell has made the right 
choice. In other languages such as Java input functions suddenly break when the 
user has a different locale setting. While for user input this might be desired, 
in my experience much of the i/o a program does is with well defined file 
formats where changing '.' to ',' just shouldn't happen.



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


Re: [Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Dan Piponi
Mauricio asked:

 Do you think 'read' (actually,
 'readsPrec'?) could be made to also
 read the international convention
 (ie., read 1,5 would also work
 besides read 1.5)?

What would you hope the value of

 read (1,2,3)::(Float,Float)

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


Re: [Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Albert Y. C. Lai

Mauricio wrote:

Do you think 'read' (actually,
'readsPrec'?) could be made to also
read the international convention


No. read and show are meant to be KISS, suitable for toy programs and 
casual debugging messages. Real applications should use or invent a 
sophisticated, general library.


(The same way real user interfaces do not use getLine.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Real World HAppS: Cabalized, Self-Demoing HAppS Tutorial (Version 3)

2008-09-16 Thread Martin Huschenbett

Hi all,

taking a look at this tutorial under Windows Vista I ran into a problem:

happs-tutorial depends on HAppS-state which again depends on the unix 
package which doesn't work under windows.


So my question is: is there another way to compile HAppS-State and 
happs-tutorial on windows?


Regards,

Martin.

Thomas Hartman schrieb:

I pushed a new version of happs-tutorial to the online demo at

http://happstutorial.com:5001 This is also on hackage: cabal install
happs-tutorial. (now version 3.)

or darcs get http://code.haskell.org/happs-tutorial for the latest

The demo/tutorial has the same basic functionality as the last release
-- just a login form essentially -- but a lot more bling now. Like
menu link items that change colors when the page is clicked. Also the
login form that gives sane error messages.

The focus for this release was on explaining how I used StringTemplate
with HAppS.

Hopefully in version 4 I'll finally get to State and Macid! And
hopefully some functionality that actually does something beyond just
showing what users have created logins :)

Thomas
___
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] Float instance of 'read'

2008-09-16 Thread Jules Bean

Mauricio wrote:

Do you think 'read' (actually,
'readsPrec'?) could be made to also
read the international convention
(ie., read 1,5 would also work
besides read 1.5)? I'm happy to
finaly use a language where I can
use words of my language to name
variables, so I wonder if we could
also make that step.


The purpose of 'read' is to read haskell notation, not to read 
locally-sensitive notation.


So the right question to ask is should we change haskell's lexical 
syntax to support locally-sensitive number notation.


IMO, the answer is no.

(1,3) would start to mean (13/10) and we'd need another notational rule 
(whitespace around commas) for numeric tuples. Feels like a painful 
special case to me.


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


Re: [Haskell-cafe] Semantic Domain, Function, and denotational model.....

2008-09-16 Thread Ryan Ingram
at time = id is not valid Haskell.  It's expositional, describing a
law that at and time fulfill.

It's like saying m = return = m when describing the Monad laws.
You can't write that directly, but it better be true!

  -- ryan

2008/9/16 Daryoush Mehrtash [EMAIL PROTECTED]:
 I can sort of see what is happening in time = O (pure (Fun id)).
 But I am not sure I understand this:

time :: Behavior Time
at time = id

 as I understand it at is a function that take Behaviour and returns
 a function that is Time - a.How can you have a function on the
 left side of the equation?

 thanks,

 Daryoush


 2008/9/16 Conal Elliott [EMAIL PROTECTED]:
 Hi Ryan,

 Thanks very much for these explanations.  Clear and right on!

 Best regards,  - Conal

 P.S. I'll be at ICFP and am looking forward to seeing folks there.

 2008/9/16 Ryan Ingram [EMAIL PROTECTED]

 The key insight is that Behavior a is not necessarily a time function;
 it's abstract.  But you can treat it as if it was one by observing it
 with at.

 In Conal's paper, the internal type of behavior is:

  -- composition of types; like (.) at the type level
  newtype O h g a = O (h (g a))

  -- function type that can directly observe some constant functions
  data Fun t a = K a | Fun (t - a)

  -- Behavior a ~~ Reactive (Fun Time a)
  type Behavior = Reactive `O` Fun Time

  -- Reactive has a current value and an event stream of values to switch
  to at particular times
  -- Then an event is just a reactive that might not have a current value
  until some time in the future.
  data Reactive a = Stepper a (Event a)
  newtype Event a = Ev (Future (Reactive a))

 Now, at the internal level, you can write the primitive time as

  time :: Behavior Time
  time = O (pure (Fun id))

 with pure from the Applicative instance for Reactive:

  pure x = Stepper x never

 never is a future that never occurs, so the reactive value never
 changes.

 From a users' point of view, all this is invisible--you only get a few
 observation functions (including at).  Internally, however, constant
 behaviors, or behaviors that contain steps that are constant, can be
 evaluated extremely quickly; once the behavior returns K x, you know
 that the result can't change until the next event in the reactive
 stream.  You only need to continuously evaluate the behavior if you
 get a Fun result.  See sinkB on page 9 of the paper to understand
 how this is used to improve performance.

 The semantic function at drives the model; it allows you to describe
 the laws for the library to fulfill very succinctly:

 at (fmap f x) = fmap f (at x)
 at (pure x) = pure x
 at (f * x) = at f * at x
 at (return x) = return x
 at (m = f) = at m = at . f
 etc.

 Similarily, for Futures, we have force :: Future a - (Time, a)

 force (fmap f z) = (t, f x) where (t,x) = force z
 force (pure x) = (minBound, x)
 force (ff * fx) = (max tf tx, f x) where (tf, f) = force ff ; (tx,
 x) = force fx
 force (return x) = (minBound, x)
 force (m = f) = (max tm tx, x) where (tm, v) = force m; (tx, x) = force
 (f v)
 etc.

 This gives the library user solid ground to stand on when reasoning
 about their code; it should do what they expect.  And it gives the
 library author a very strong goal to shoot for: just fulfill these
 laws, and the code is correct!  This allows radical redesigns of the
 internals of the system while maintaining a consistent and intuitive
 interface that reuses several classes that the user is hopefully
 already familiar with: monoids, functors, applicative functors, and
 monads.

  -- ryan

 2008/9/16 Daryoush Mehrtash [EMAIL PROTECTED]:
  ّ I don't follow the at and  type B a.  Behavior a itself is a
  time function.   At least in the version of the code that was
  developed in Pual Hudak's Haskell School of Expression it was defined
  as:
 
  newtype Behavior a
= Behavior (([Maybe UserAction],[Time]) - [a])
 
  In a function like time you can see that the at function makes things
  simpler.
 
  In the original version  time was defined as:
 
  time :: Behavior Time
  time = Behavior (\(_,ts) - ts)
 
  In Conal's paper
 
  time :: Behavior Time
  at time = id
 
  Comparing the two implementation of the time, it seems to me that at
  and type B a has put the design on a more solid ground.  But I don't
  quite understand the thought process, or the principal behind what is
  happening.
 
  daryoush
 
 
  On Mon, Sep 15, 2008 at 10:46 AM, Ryan Ingram [EMAIL PROTECTED]
  wrote:
  Here's a quick overview that might help you.
 
  For a reactive behavior, we have two types to think about:
 
  type B a = Time - a
 (the semantic domain)
 
  data Behavior a = ?
 (the library's implementation).
  at :: Behavior a - B a
 (observation function)
 
  This is really just classic information hiding as you would do with
  any abstract data type.  Consider a simple stack data structure that
  supports push and pop.
 
  data S a = S
  { popS :: Maybe (a, S a)
  , pushS :: a - S a
  }
 

Re: [Haskell-cafe] Semantic Domain, Function, and denotational model.....

2008-09-16 Thread Conal Elliott
exactly.  it's a specification of the denotational semantics of time.  any
valid implementation must satisfy such properties.

2008/9/16 Ryan Ingram [EMAIL PROTECTED]

 at time = id is not valid Haskell.  It's expositional, describing a
 law that at and time fulfill.

 It's like saying m = return = m when describing the Monad laws.
 You can't write that directly, but it better be true!

  -- ryan

 2008/9/16 Daryoush Mehrtash [EMAIL PROTECTED]:
  I can sort of see what is happening in time = O (pure (Fun id)).
  But I am not sure I understand this:
 
 time :: Behavior Time
 at time = id
 
  as I understand it at is a function that take Behaviour and returns
  a function that is Time - a.How can you have a function on the
  left side of the equation?
 
  thanks,
 
  Daryoush
 
 
  2008/9/16 Conal Elliott [EMAIL PROTECTED]:
  Hi Ryan,
 
  Thanks very much for these explanations.  Clear and right on!
 
  Best regards,  - Conal
 
  P.S. I'll be at ICFP and am looking forward to seeing folks there.
 
  2008/9/16 Ryan Ingram [EMAIL PROTECTED]
 
  The key insight is that Behavior a is not necessarily a time function;
  it's abstract.  But you can treat it as if it was one by observing it
  with at.
 
  In Conal's paper, the internal type of behavior is:
 
   -- composition of types; like (.) at the type level
   newtype O h g a = O (h (g a))
 
   -- function type that can directly observe some constant functions
   data Fun t a = K a | Fun (t - a)
 
   -- Behavior a ~~ Reactive (Fun Time a)
   type Behavior = Reactive `O` Fun Time
 
   -- Reactive has a current value and an event stream of values to
 switch
   to at particular times
   -- Then an event is just a reactive that might not have a current
 value
   until some time in the future.
   data Reactive a = Stepper a (Event a)
   newtype Event a = Ev (Future (Reactive a))
 
  Now, at the internal level, you can write the primitive time as
 
   time :: Behavior Time
   time = O (pure (Fun id))
 
  with pure from the Applicative instance for Reactive:
 
   pure x = Stepper x never
 
  never is a future that never occurs, so the reactive value never
  changes.
 
  From a users' point of view, all this is invisible--you only get a few
  observation functions (including at).  Internally, however, constant
  behaviors, or behaviors that contain steps that are constant, can be
  evaluated extremely quickly; once the behavior returns K x, you know
  that the result can't change until the next event in the reactive
  stream.  You only need to continuously evaluate the behavior if you
  get a Fun result.  See sinkB on page 9 of the paper to understand
  how this is used to improve performance.
 
  The semantic function at drives the model; it allows you to describe
  the laws for the library to fulfill very succinctly:
 
  at (fmap f x) = fmap f (at x)
  at (pure x) = pure x
  at (f * x) = at f * at x
  at (return x) = return x
  at (m = f) = at m = at . f
  etc.
 
  Similarily, for Futures, we have force :: Future a - (Time, a)
 
  force (fmap f z) = (t, f x) where (t,x) = force z
  force (pure x) = (minBound, x)
  force (ff * fx) = (max tf tx, f x) where (tf, f) = force ff ; (tx,
  x) = force fx
  force (return x) = (minBound, x)
  force (m = f) = (max tm tx, x) where (tm, v) = force m; (tx, x) =
 force
  (f v)
  etc.
 
  This gives the library user solid ground to stand on when reasoning
  about their code; it should do what they expect.  And it gives the
  library author a very strong goal to shoot for: just fulfill these
  laws, and the code is correct!  This allows radical redesigns of the
  internals of the system while maintaining a consistent and intuitive
  interface that reuses several classes that the user is hopefully
  already familiar with: monoids, functors, applicative functors, and
  monads.
 
   -- ryan
 
  2008/9/16 Daryoush Mehrtash [EMAIL PROTECTED]:
   ّ I don't follow the at and  type B a.  Behavior a itself is a
   time function.   At least in the version of the code that was
   developed in Pual Hudak's Haskell School of Expression it was defined
   as:
  
   newtype Behavior a
 = Behavior (([Maybe UserAction],[Time]) - [a])
  
   In a function like time you can see that the at function makes
 things
   simpler.
  
   In the original version  time was defined as:
  
   time :: Behavior Time
   time = Behavior (\(_,ts) - ts)
  
   In Conal's paper
  
   time :: Behavior Time
   at time = id
  
   Comparing the two implementation of the time, it seems to me that
 at
   and type B a has put the design on a more solid ground.  But I
 don't
   quite understand the thought process, or the principal behind what is
   happening.
  
   daryoush
  
  
   On Mon, Sep 15, 2008 at 10:46 AM, Ryan Ingram [EMAIL PROTECTED]
   wrote:
   Here's a quick overview that might help you.
  
   For a reactive behavior, we have two types to think about:
  
   type B a = Time - a
  (the semantic domain)
  
   data Behavior a = ?
  (the library's 

Re: [Haskell-cafe] Float instance of 'read'

2008-09-16 Thread Bryan O'Sullivan
On Tue, Sep 16, 2008 at 5:29 AM, Mauricio [EMAIL PROTECTED] wrote:


 Do you think 'read' (actually,
 'readsPrec'?) could be made to also
 read the international convention
 (ie., read 1,5 would also work
 besides read 1.5)?


No, as read is really intended to be a language-level tool, not something
that you should expose to end users. For locale-aware number input and
formatting, you'd want to do something else.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Semantic Domain, Function, and denotational model.....

2008-09-16 Thread Greg Meredith
Daryoush,

Hopefully, the other replies about proving the monad laws already answered
your previous question: yes!

As for notions of semantic domain and denotational model, these ideas go
back quite a ways; but, were given solid footing by Dana
Scotthttp://en.wikipedia.org/wiki/Dana_Scott.
In a nutshell, we have essentially three views of a computation

   - Operational http://en.wikipedia.org/wiki/Operational_semantics --
   computation is captured in a program and rules for executing it
   - Logical http://en.wikipedia.org/wiki/Proof-theoretic_semantics --
   computation is captured in a proof and rules for normalizing it
   - Denotational http://en.wikipedia.org/wiki/Denotational_semantics --
   computation is captured as a (completely unfolded) mathematical structure

In the latter view we think of computations/programs as denoting some
(usually infinitary) mathematical object. Our
aimhttp://en.wikipedia.org/wiki/Domain_theoryis to completely define
the meaning of programs in terms of maps between
their syntactic representation and the mathematical objects their syntax is
intended to denote. (Notationally, one often writes such maps as [| - |] :
Program - Denotation.) For example, we model terms in the lambda calculus
as elements in a D-infinity domain or Bohm trees or ... . Or, in more modern
parlance, we model terms in the lambda calculus as morphisms in some
Cartesian closed category, and the types of those terms as objects in said
category. The gold standard of quality of such a model is full
abstractionhttp://en.wikipedia.org/wiki/Denotational_semantics#Full_abstraction--
when the denotational notion of equivalence exactly coincides with an
intended operational notion of equivalence. In symbols,


   - P ~ Q = [| P |] = [| Q |], where ~ and = are the operational and
   denotational notions of equivalence, respectively


The techniques of denotational semantics have been very fruitful, but
greatly improved by having to rub elbows with operational characterizations.
The original proposals for denotational models of the lambda calculus were
much too arms length from the intensional structure implicit in the notion
of computation and thus failed to achieve full abstraction even for toy
models of lambda enriched with naturals and booleans (cf the so-called full
abstraction for PCF
problemhttp://en.wikipedia.org/wiki/Programming_language_for_Computable_Functions).
On the flip side, providing a better syntactic exposure of the use of
resources -- ala linear logic -- aided the denotational programme.

More generally, operational models fit neatly into two ready-made notions of
equivalence

   - contextual
equivalencehttp://encyclopedia2.thefreedictionary.com/Contextual+equivalence--
behaves the same in all contexts
   - bisimulation http://en.wikipedia.org/wiki/Bisimulation -- behaves the
   same under all observations

Moreover, these can be seen to coincide with ready-made notions of
equivalence under the logical view of programs. Except for syntactically
derived initial/final denotational models -- the current theory usually
finds a more home-grown denotational notion of equivalence. In fact, i
submit that it is this very distance from the syntactic presentation that
has weakened the more popular understanding of denotational models to just
this -- whenever you have some compositionally defined map from one
representation to another that respects some form of equivalence, the target
is viewed as the denotation.

Best wishes,

--greg

Date: Mon, 15 Sep 2008 10:13:53 -0700
From: Daryoush Mehrtash [EMAIL PROTECTED]
Subject: Re: [Haskell-cafe] Semantic Domain, Function,  and
   denotational model.
To: Ryan Ingram [EMAIL PROTECTED]
Cc: Haskell Cafe haskell-cafe@haskell.org
Message-ID:
   [EMAIL PROTECTED]
Content-Type: text/plain; charset=ISO-8859-1

Interestingly, I was trying to read his paper when I realized that I
needed to figure out the meaning of denotational model, semantic
domain, semantic functions.  Other Haskell books didn't talk about
design in those terms, but obviously for him this is how he is driving
his design.   I am looking for a simpler tutorial, text book like
reference on the topic.

Daryoush

On Mon, Sep 15, 2008 at 1:33 AM, Ryan Ingram [EMAIL PROTECTED] wrote:
 I recommend reading Conal Elliott's Efficient Functional Reactivity
 paper for an in-depth real-world example.

 http://www.conal.net/papers/simply-reactive

  -- ryan

 On Sun, Sep 14, 2008 at 11:31 AM, Daryoush Mehrtash [EMAIL PROTECTED]
wrote:
 I have been told that for a Haskell/Functional programmer the process
 of design starts with defining Semantic Domain, Function, and
 denotational model of the problem.  I have done some googling on the
 topic but haven't found a good reference on it.I would appreciate
 any good references on the topic.

 thanks,

 daryoush

 ps.  I have found referneces like
 http://en.wikibooks.org/wiki/Haskell/Denotational_semantics  which
 talks about semantic domain for the 

Re: [Haskell-cafe] How to check if two Haskell files are the same?

2008-09-16 Thread Antoine Latter
On Tue, Sep 16, 2008 at 9:30 AM, Mauricio [EMAIL PROTECTED] wrote:
 Hi,

 I would like to write a Haskell pretty-printer,
 using standard libraries for that. How can I
 check if the original and the pretty-printed
 versions are the same? For instance, is there
 a file generated by GHC at the compilation
 pipe that is always guaranteed to have the
 same MD5 hash when it comes from equivalent
 source?

I don't know the answers to your question, but if you're looking for
inspiration on your project you should check out the following two
packages:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/haskell-src
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/haskell-src-exts

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


Re: [Haskell-cafe] How to check if two Haskell files are the same?

2008-09-16 Thread Brandon S. Allbery KF8NH

On 2008 Sep 16, at 10:30, Mauricio wrote:

I would like to write a Haskell pretty-printer,
using standard libraries for that. How can I
check if the original and the pretty-printed
versions are the same? For instance, is there
a file generated by GHC at the compilation
pipe that is always guaranteed to have the
same MD5 hash when it comes from equivalent
source?


Compare .hi files?

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] How to check if two Haskell files are the same?

2008-09-16 Thread Philip Weaver
On Tue, Sep 16, 2008 at 7:30 AM, Mauricio [EMAIL PROTECTED] wrote:

 Hi,

 I would like to write a Haskell pretty-printer,
 using standard libraries for that. How can I
 check if the original and the pretty-printed
 versions are the same? For instance, is there
 a file generated by GHC at the compilation
 pipe that is always guaranteed to have the
 same MD5 hash when it comes from equivalent
 source?


I don't know, but you can parse the resulting concrete syntax and compare
the original abstract syntax to the new abstract syntax.



 Thanks,
 Maurício

 ___
 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] Mac OS X dylib woes

2008-09-16 Thread John MacFarlane
I'm hoping some Haskell developers who use Macs can help me with this
one. I can install pcre-light just fine using cabal install. But when I
try to use it, I get this error:

GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
:Loading package base ... linking ... done.
Prelude :m Text.Regex.PCRE.Light.Char8
Prelude Text.Regex.PCRE.Light.Char8 compile h. []
Loading package array-0.1.0.0 ... linking ... done.
Loading package bytestring-0.9.0.1 ... linking ... done.
Loading package pcre-light-0.3.1 ... can't load .so/.DLL for: pcre 
(dlopen(libpcre.dylib, 10): image not found)

OK, so it can't find the pcre library (which is in /opt/local/lib).
I can fix that:

export DYLD_LIBRARY_PATH=/opt/local/lib

Now it works. But other things are broken! For example, I can't run vim,
which looks for a library called libJPEG.dylib and now finds libjpeg.dylib
in /opt/local/lib (case-insensitive file system!).

The apple website recommends against setting DYLD_LIBRARY_PATH.
Instead, they say, the paths to the libraries should be hard-coded into
the binary:
http://discussions.apple.com/thread.jspa?threadID=1670523tstart=0

I'm sure others have had the same problem.  What's the solution?

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


Re: [Haskell-cafe] How to check if two Haskell files are the same?

2008-09-16 Thread John Van Enk
Before you reinvent the wheel, have you looked at Language.Haskell.Pretty?

http://haskell.org/ghc/docs/latest/html/libraries/haskell-src/Language-Haskell-Pretty.html

On Tue, Sep 16, 2008 at 10:30 AM, Mauricio [EMAIL PROTECTED] wrote:

 Hi,

 I would like to write a Haskell pretty-printer,
 using standard libraries for that. How can I
 check if the original and the pretty-printed
 versions are the same? For instance, is there
 a file generated by GHC at the compilation
 pipe that is always guaranteed to have the
 same MD5 hash when it comes from equivalent
 source?

 Thanks,
 Maurício

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




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


[Haskell-cafe] haskell blas bindings: does iomatrix gemv transposing of matrix a?

2008-09-16 Thread Anatoly Yakovenko
Hey Patric,

Thanks for your great work on the blas bidnings.  I have a question on
gemv.  I thought its possible for blas to transpose the input matrix
before doing the multiplication.  Is it possible to do that with the
haskell bindings?  Or am I mistaken in how gemv is used

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


Re: [Haskell-cafe] GHC trouble on Leopard

2008-09-16 Thread Jason Dusek
  Could you provide us with the command line you were using?

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


Re: [Haskell-cafe] Re: Comparing GADTs for Eq and Ord

2008-09-16 Thread Tom Hawkins
Thanks for all the input.  It helped me arrive at the following
solution.  I took the strategy of converting the parameterized type
into an unparameterized type which can be easily compared for Eq and
Ord.  The unparameterized type enumerates the possible Const types
with help from an auxiliary type class.

-- The primary Expr type.
data Expr a where
  Const :: ExprConst a = a - Expr a
  Equal :: Expr a - Expr a - Expr Bool

-- An untyped Expr used to compute Eq and Ord of the former.
-- Note each type of constant is enumerated.
data UExpr
  = UConstBool   Bool
  | UConstIntInt
  | UConstFloat  Float
  | UEqual UExpr UExpr
  deriving (Eq, Ord)

-- A type class to assist in converting Expr to UExpr.
classExprConst a where uexprConst :: a - UExpr
instance ExprConst Bool  where uexprConst = UConstBool
instance ExprConst Int   where uexprConst = UConstInt
instance ExprConst Float where uexprConst = UConstFloat

-- The conversion function.
uexpr :: Expr a - UExpr
uexpr (Const a) = uexprConst a
uexpr (Equal a b) = UEqual (uexpr a) (uexpr b)

-- Finally the implementation of Eq and Ord for Expr.
instance Eq  (Expr a) where a == b = uexpr a == uexpr b
instance Ord (Expr a) where compare a b = compare (uexpr a) (uexpr b)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC trouble on Leopard

2008-09-16 Thread Manuel M T Chakravarty

Miguel,


I tried to compile some code on Mac Os X (Intel) Leopard.
I have GHC 6.8.3 installed - the installer from GHC webpage  
(GHC-6.8.3-i386.pkg).


But when I run make I get this error

ghc-6.8.3: could not execute: /Library/Frameworks/GHC.framework/ 
Versions/608/usr/lib/ghc-6.8.3/ghc-asm


This is not a common problem.  I suspect that either your installation  
somehow got corrupt or you somehow changed your Perl installation.   
(The file in question is a Perl script.)


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


[Haskell-cafe] Predicativity?

2008-09-16 Thread Wei Hu
Hello,

I only have a vague understanding of predicativity/impredicativity, but cannot 
map this concept to practice.

We know the type of id is forall a. a - a. I thought id could not be applied 
to itself under predicative polymorphism. But Haksell and OCaml both type check 
(id id) with no problem. Is my understanding wrong? Can you show an example 
that doesn't type check under predicative polymorphism, but would type check 
under impredicative polymorphism?

Thanks!

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


Re: Hyena Status? Re: [Haskell-cafe] Starting Haskell with a web application

2008-09-16 Thread Johan Tibell
On Tue, Sep 16, 2008 at 11:15 AM, Donnie Jones [EMAIL PROTECTED] wrote:
 Hello Johan Tibell,

 Hyena looks very interesting.  From the github tracking, you've been
 working...  Maybe a release soon?

I'm working towards it. I've been very busy at work lately but it's
getting there. I need to do some more optimization work. The holy
grail is 10k requests per second.

 Also, I saw your slides from the 'Left-fold enumerators' presentation at
 Galois.  Maybe include the slides in the docs/ for a release?

I make sure the project is documented in the best way I can come up with. :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Python's big challenges, Haskell's big advantages?

2008-09-16 Thread Don Stewart

http://www.heise-online.co.uk/open/Shuttleworth-Python-needs-to-focus-on-future--/news/111534

cloud computing, transactional memory and future multicore processors

Get writing that multicore, STM, web app code!

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