[Haskell-cafe] buildExpressionParser prefix recursion

2009-12-01 Thread Warren Harris
I was wondering why Parsec's buildExpressionParser doesn't allow  
prefix expressions to be handled recursively, e.g. given a prefix "!"  
operation, it seems that "!!a" could parse without requiring  
parentheses ("!(!a)"). Is there an easy way to extend it? (I have a  
rich expression grammar I'd like to parse which includes several  
prefix forms, and it would be a shame to have to abandon  
buildExpressionParser since it is so concise and convenient.) Thanks,


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


Re: [Haskell-cafe] university courses on type families/GADTs?

2009-12-01 Thread Stefan Holdermans

Tom,

I was wondering whether there are any universities that teach about  
Haskell type families or GADTs?


I'm quite sure at least GADTs are covered in INFOMAFP, the graduate  
course on Advanced Functional Programming at UU:


  http://www.cs.uu.nl/docs/vakken/afp

Cheers,

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


Re: [Haskell-cafe] Trying to sort out multiparameter type classes and their instances

2009-12-01 Thread Jeremy Fitzhardinge
On 12/01/09 17:38, Daniel Fischer wrote:
> Am Mittwoch 02 Dezember 2009 01:43:04 schrieb Jeremy Fitzhardinge:
>   
>> On 12/01/09 15:12, Daniel Fischer wrote:
>> 
>>> Am Dienstag 01 Dezember 2009 23:34:46 schrieb Jeremy Fitzhardinge:
>>>   
 I'm playing around with some types to represent a game board (like Go,
 Chess, Scrabble, etc).

 I'm using a type class to represent the basic Board interface, so I can
 change the implementation freely:

 class Board b pos piece where
 -- Update board with piece played at pos
 play :: b pos piece -> pos -> piece -> b pos piece
 
>>> So the parameter b of the class is a type constructor taking two types
>>> and constructing a type from those.
>>>   
>> Yep.
>>
>> 
>>> IOW, it's a type constructor of kind (* -> * -> *), like (->) or Either.
>>> (* is the kind of types [Int, Char, Either Bool (), Double -> Rational ->
>>> Int, ...]
>>>
>>> [...]
>>>
>>>   
 but ghci complains:
 board.hs:34:15:
 Kind mis-match
 Expected kind `* -> * -> *', but `pos -> Maybe piece' has kind `*'
 In the instance declaration for `Board (pos
 -> Maybe piece) pos piece'
 
>>> Yes, as said above.
>>> (pos -> Maybe piece) is a *type*, but the type class expects a type
>>> constructor of kind (* -> * ->*) here.
>>>   
>> I thought "(pos -> Maybe piece) pos piece" would provide the 3 type
>> arguments to Board.
>>
>> Oh, I see my mistake.  I was seeing "b pos piece" as type parameters for
>> Board, but actually Board is just taking a single parameter of kind * ->
>> * -> *.
>> 
> No.
>
> class Board b pos piece where
>  -- Update board with piece played at pos
>  play :: b pos piece -> pos -> piece -> b pos piece
>
> the class Board takes three parameters: b, pos and piece.
>
> The (first) argument of play is the type (kind *)
>
> b pos piece
>
> Thus b is a type constructor taking two arguments. Since the arguments it 
> takes, pos and 
> piece, appear as the types of the second and third argument of play, these 
> two must be 
> plain types (kind *).
>
> Thus
>
> b :: * -> * -> *
>
> But in your instance declaration, in the position of b, you pass
>
> (pos -> Maybe piece), which is a type (kind *) and not a binary type 
> constructor as 
> required by the class declaration.
> If Haskell had type-level lambdas, what you would have needed to pass there is
>
> (/\ t1 t2. (t1 -> Maybe t2))
>
> (or, if Haskell had type-constructor composition: ((. Maybe) . (->)) )
>
> However, Haskell has neither type-level lambdas nor type-constructor 
> composition, so you 
> can't.
> You can only emulate that by using newtypes, hence Method 1 in my reply.
>
>   
>> 
>>> Method 2: Multiparameter type class with functional dependencies and
>>> suitable kinds
>>>
>>> class Board b pos piece | b -> pos, b -> piece where
>>> play :: b -> pos -> piece -> b
>>> at :: b -> pos -> Maybe piece
>>> empty :: b
>>>
>>> instance (Eq pos) => Board (pos -> Maybe piece) pos piece where
>>> play b pos piece = \p -> if p == pos then Just piece else b p
>>> at = id
>>> empty = const Nothing
>>>
>>> requires {-# LANGUAGE FlexibleInstances #-}
>>>
>>> Not necessarily ideal either.
>>>   
>> OK, but that's pretty much precisely what I was aiming for.   I'm not
>> sure I understand what the difference between
>>
>> play :: b pos piece -> pos -> piece -> b pos piece
>>
>> and
>>
>> play :: b -> pos -> piece -> b
>>
>> is.  Does adding type params to b here change its kind?
>> 
> That's not quite correctly expressed, but basically, yes, that's it.
>   

What would be the correct way to express it?

> With the signature
>
> play :: b pos piece -> pos -> piece -> b pos piece,
>
> b must be a type expression of arity 2, taking two plain types as arguments, 
> that is, a 
> type constructor of kind (* -> * -> *), like Either, State, (->) or a 
> partially applied 
> type constructor of higher arity like ((,,,) Int (Char ->Bool)) [the 
> quadruple constructor 
> (,,,) of kind (* -> * -> * -> * -> *) applied to two types, leaving two slots 
> open].
>   

OK, I think I understand now.  It helps explain my questions about the
types of "first" and "second", which I always use on tuples, but their
types are much more general.


>>> Method 3: Associated type families
>>>
>>> {-# LANGUAGE TypeFamilies, FlexibleInstances #-}
>>> module Board where
>>>
>>> class Board b where
>>> type Pos b :: *
>>> type Piece b :: *
>>> play :: b -> Pos b -> Piece b -> b
>>> at :: b -> Pos b -> Maybe (Piece b)
>>> empty :: b
>>>
>>> instance (Eq pos) => Board (pos -> Maybe piece) where
>>> type Pos (pos -> Maybe piece) = pos
>>> type Piece (pos -> Maybe piece) = piece
>>> play b pos piece = \p -> if p == pos then Just piece else b p
>>> at b p = b p
>>> empty _ = Nothing
>>>
>>> I would try that first.
>>

Re: [Haskell-cafe] university courses on type families/GADTs?

2009-12-01 Thread Manuel M T Chakravarty
Tom Schrijvers wrote,
> I was wondering whether there are any universities that teach about Haskell 
> type families or GADTs?

I do in my course "Language-based Software Safety" (both TFs and GADTs).  It's 
an advanced, research-oriented course for 4th year undergraduate and for 
postgraduate students.  (It wasn't offered last year and this year, but will be 
again offered next year.)

Manuel

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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 03:28:04 schrieb Michael Mossey:
> Daniel Fischer wrote:
> >> getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)
> >
> > Yeah, that screams State Monad.
>
> Hi, thanks for all the advice.
>
> I was hoping my AssignedNumbers "class" would be useful with many data
> structures. In other words I would have
>
> data State1 = State1 { a :: AssignedNumbers, b :: AssignedNumbers, ... }
> data State2 = State2 { c :: AssignedNumbers, d :: AssignedNumbers, ... }
>
> func1 :: State State1 Int
> func1 = do
> ... something using a and b ...
>
> func2 :: State State2 Int
> func2 = do
> ... something using c and d ...
>
> So I thought maybe I could defined a function like
>
> nextNumber :: MonadState s m => (s -> AssignedNumbers) -> (AssignedNumbers
> -> s) -> m Int
> nextNumber retreive putBack = ...
>
> and have it be useful in both "State State1 a" and "State State2 a" monads,
> but defining the retrieve and putBack functions isn't pretty.
>
> I will try to grok Robert's reply also. Maybe he has something addressing
> this.

Definitely.

data AssignType = Oscillator | Table | Thingamajig
deriving (Eq, Ord, Ix)

data MusicState
= MS
{ assignedNumbers :: Array AssignType AssignedNumbers
, other stuff
} deriving (Everything you need)

fetchNumber :: String -> AssignType -> State MusicState Int
fetchNumber str ty = do
an <- gets ((! ty) . assignedNumbers)
let (i,newAn) = getNumber str an
modify (\ms -> ms{ assignedNumbers = assignedNumbers ms // [(ty,newAn)] })
return i

doSomeMusicStuff aString1 aString2 = do
o <- fetchNumber aString1 Oscillator
t <- fetchNumber aString2 Table
return (o,t)

>
> Mike

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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Michael Mossey



Daniel Fischer wrote:

getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)


Yeah, that screams State Monad.



Hi, thanks for all the advice.

I was hoping my AssignedNumbers "class" would be useful with many data 
structures. In other words I would have


data State1 = State1 { a :: AssignedNumbers, b :: AssignedNumbers, ... }
data State2 = State2 { c :: AssignedNumbers, d :: AssignedNumbers, ... }

func1 :: State State1 Int
func1 = do
   ... something using a and b ...

func2 :: State State2 Int
func2 = do
   ... something using c and d ...

So I thought maybe I could defined a function like

nextNumber :: MonadState s m => (s -> AssignedNumbers) -> (AssignedNumbers 
-> s) -> m Int

nextNumber retreive putBack = ...

and have it be useful in both "State State1 a" and "State State2 a" monads, 
but defining the retrieve and putBack functions isn't pretty.


I will try to grok Robert's reply also. Maybe he has something addressing this.

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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 02:01:29 schrieb Michael P Mossey:
> Perhaps someone could either (1) help me do what I'm trying to do, or (2)
> show me a better way.
>
> I have a problem that is very state-ful and I keep thinking of it as OO,
> which is driving me crazy. Haskell is several times harder to use than
> Python in this instance, probably because I'm doing it wrong.

If you want to do something very stateful, it is a bit cumbersome in Haskell.
Perhaps it is the wrong approach and you can do it with much less state.
Or perhaps, this is possible, too, it is not a task for which Haskell is well 
suited.
Or perhaps you're really doing it wrong because of lack of experience.

>
> To give you a larger context, this problem is essentially compiling a
> description of music (my own) into a kind of music-machine-language
> (CSound). CSound is relatively untidy.
>
> In this one example, in a OO way of thinking, I have data called
> AssignedNumbers that assigns integers to unique strings and keeps track of
> the used integers and next available integer (the choice of available
> integer could follow a number of conventions so I wanted to hide that in an
> ADT.) So it has an associated function:
>
> getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)

Yeah, that screams State Monad.

>
> What getNumber does is:
>
>- check if the string already has a number assigned to it. If so, return
> that number.
>
>- if not, pick the next available number.
>
>- in all cases, return the possibly changed state of AssignedNumbers
>
> Then in a larger data structure, it contains fields of type
> AssignedNumbers. Like
>
> data MusicStuff = MusicStuff
>{ oscillatorNumbers :: AssignedNumbers
>, tableNumbers :: AssignedNumbers
>, ... }
>
> I'm using MusicStuff in a State monad, so I might write a function like
>
> doSomeMusicStuff :: String -> String -> State MusicStuff (Int,Int)
> doSomeMusicStuff aString1 aString2 = do
> ms <- get
> (o1,newOscNums) = getNumber aString1 (oscillatorNumbers ms)
> (t1,newTabNums) = getNumber aString2 (tableNumbers ms)
> put ms { oscillatorNumbers = newOscNums
>, tableNumbers = newTabNums }
> return (o1,t1)
>
> For what it does, this is extremely verbose and filled with distracting
> visual content. And this is just a very simple example---my real problem is
> several times more state-ful. Is there a better way?

If you're doing that in many places, factor out the methods

getOscillatorNumber :: String -> State MusicStuff Int
getOscillatorNumber str = do
ms <- get
let on = oscilatorNumbers ms
(o1,newOn) = getNumber str on
put (ms{ oscillatorNumbers = newOn })
return o1

same for tableNumbers etc.

Then 

doSomeMusicStuff aString1 aString2 = do
o <- getOscillatorNumber aString1
t <- getTableNumber aString2
return (o,t)

and the verbosity is moved to one place. That isn't worthwhile for seldomly 
used stuff, of 
course.

>
> Note that in Python it would be a method
>
> def doMusicStuff( self, s1, s2 ) :
> return (self.oscillatorNumbers.next(s1),
> self.oscillatorNumbers.next(s2))
>

Yeah, mutability gives brevity here.

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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Robert Greayer
On Tue, Dec 1, 2009 at 9:01 PM, Robert Greayer  wrote:

>
>
> On Tue, Dec 1, 2009 at 8:01 PM, Michael P Mossey 
> wrote:
>
>> Perhaps someone could either (1) help me do what I'm trying to do, or (2)
>> show me a better way.
>>
>> I have a problem that is very state-ful and I keep thinking of it as OO,
>> which is driving me crazy. Haskell is several times harder to use than
>> Python in this instance, probably because I'm doing it wrong.
>>
>> To give you a larger context, this problem is essentially compiling a
>> description of music (my own) into a kind of music-machine-language
>> (CSound). CSound is relatively untidy.
>>
>> In this one example, in a OO way of thinking, I have data called
>> AssignedNumbers that assigns integers to unique strings and keeps track of
>> the used integers and next available integer (the choice of available
>> integer could follow a number of conventions so I wanted to hide that in an
>> ADT.) So it has an associated function:
>>
>> getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)
>>
>> What getNumber does is:
>>
>>  - check if the string already has a number assigned to it. If so, return
>> that number.
>>
>>  - if not, pick the next available number.
>>
>>  - in all cases, return the possibly changed state of AssignedNumbers
>>
>> Then in a larger data structure, it contains fields of type
>> AssignedNumbers. Like
>>
>> data MusicStuff = MusicStuff
>>  { oscillatorNumbers :: AssignedNumbers
>>  , tableNumbers :: AssignedNumbers
>>  , ... }
>>
>> I'm using MusicStuff in a State monad, so I might write a function like
>>
>> doSomeMusicStuff :: String -> String -> State MusicStuff (Int,Int)
>> doSomeMusicStuff aString1 aString2 = do
>>   ms <- get
>>   (o1,newOscNums) = getNumber aString1 (oscillatorNumbers ms)
>>   (t1,newTabNums) = getNumber aString2 (tableNumbers ms)
>>   put ms { oscillatorNumbers = newOscNums
>>  , tableNumbers = newTabNums }
>>   return (o1,t1)
>>
>> For what it does, this is extremely verbose and filled with distracting
>> visual content. And this is just a very simple example---my real problem is
>> several times more state-ful. Is there a better way?
>>
>
> As a quick observation, you might consider changing getNumber to be
> something like:
>
> nextNumber :: String -> NumberGroup -> State MusicStuff Int
>
> where NumberGroup is something like
>
> data NumberGroup = OscNums | TabNums |...
>
> nextNumber updates the appropriate set of numbers in MusicStuff and returns
> the number. doSomeMusicStuff then becomes:
>
> doSomeMusicStuff aString1 aString2 = (,) `liftM` nextNumber OscNums `ap`
> nextNumber TabNums
>
> or better yet (applicatively)
>
> doSomeMusicStuff aString1 aString2 = (,) <$> nextNumber OscNums <*>
> nextNumber TabNums
>
>

Oops, that's:

doSomeMusicStuff aString1 aString2 =
(,) `liftM` nextNumber aString1 OscNums `ap` nextNumber aString2 TabNums

or:

doSomeMusicStuff aString1 aString2 =
(,) <$> nextNumber aString1 OscNums <*> nextNumber aString2 TabNums
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Robert Greayer
On Tue, Dec 1, 2009 at 8:01 PM, Michael P Mossey wrote:

> Perhaps someone could either (1) help me do what I'm trying to do, or (2)
> show me a better way.
>
> I have a problem that is very state-ful and I keep thinking of it as OO,
> which is driving me crazy. Haskell is several times harder to use than
> Python in this instance, probably because I'm doing it wrong.
>
> To give you a larger context, this problem is essentially compiling a
> description of music (my own) into a kind of music-machine-language
> (CSound). CSound is relatively untidy.
>
> In this one example, in a OO way of thinking, I have data called
> AssignedNumbers that assigns integers to unique strings and keeps track of
> the used integers and next available integer (the choice of available
> integer could follow a number of conventions so I wanted to hide that in an
> ADT.) So it has an associated function:
>
> getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)
>
> What getNumber does is:
>
>  - check if the string already has a number assigned to it. If so, return
> that number.
>
>  - if not, pick the next available number.
>
>  - in all cases, return the possibly changed state of AssignedNumbers
>
> Then in a larger data structure, it contains fields of type
> AssignedNumbers. Like
>
> data MusicStuff = MusicStuff
>  { oscillatorNumbers :: AssignedNumbers
>  , tableNumbers :: AssignedNumbers
>  , ... }
>
> I'm using MusicStuff in a State monad, so I might write a function like
>
> doSomeMusicStuff :: String -> String -> State MusicStuff (Int,Int)
> doSomeMusicStuff aString1 aString2 = do
>   ms <- get
>   (o1,newOscNums) = getNumber aString1 (oscillatorNumbers ms)
>   (t1,newTabNums) = getNumber aString2 (tableNumbers ms)
>   put ms { oscillatorNumbers = newOscNums
>  , tableNumbers = newTabNums }
>   return (o1,t1)
>
> For what it does, this is extremely verbose and filled with distracting
> visual content. And this is just a very simple example---my real problem is
> several times more state-ful. Is there a better way?
>

As a quick observation, you might consider changing getNumber to be
something like:

nextNumber :: String -> NumberGroup -> State MusicStuff Int

where NumberGroup is something like

data NumberGroup = OscNums | TabNums |...

nextNumber updates the appropriate set of numbers in MusicStuff and returns
the number. doSomeMusicStuff then becomes:

doSomeMusicStuff aString1 aString2 = (,) `liftM` nextNumber OscNums `ap`
nextNumber TabNums

or better yet (applicatively)

doSomeMusicStuff aString1 aString2 = (,) <$> nextNumber OscNums <*>
nextNumber TabNums
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Michael Mossey
Thanks for the reply. Was there something specific you were referring to, 
or just the idea that he wrote Haskore? Haskore is not very closely related 
to what I'm trying to do. I believe he has a CSound back end for Haskore, 
but it is in a rough state and not closely related to what I'm trying to 
do. Most computer music packages have a fairly well-defined idea of a 
musical event, and events usually get translated one-to-one into another 
language. I have a quite messy problem which is describable as a big state 
machine, at least in the way I think of it. An input "event" can trigger a 
cascade of changes to the state. Channel numbers must be assigned and 
tracked, table numbers as well, decisions about whether to create a new 
table or re-use an old one, global variables and commands added and/or 
modified, etc. So I am hoping for a comment from that perspective.


Thanks,
Mike

Casey Hawthorne wrote:

Please check out Paul Hudak's page.

http://cs-www.cs.yale.edu/homes/hudak-paul/


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


Re: [Haskell-cafe] Trying to sort out multiparameter type classes and their instances

2009-12-01 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 01:43:04 schrieb Jeremy Fitzhardinge:
> On 12/01/09 15:12, Daniel Fischer wrote:
> > Am Dienstag 01 Dezember 2009 23:34:46 schrieb Jeremy Fitzhardinge:
> >> I'm playing around with some types to represent a game board (like Go,
> >> Chess, Scrabble, etc).
> >>
> >> I'm using a type class to represent the basic Board interface, so I can
> >> change the implementation freely:
> >>
> >> class Board b pos piece where
> >> -- Update board with piece played at pos
> >> play :: b pos piece -> pos -> piece -> b pos piece
> >
> > So the parameter b of the class is a type constructor taking two types
> > and constructing a type from those.
>
> Yep.
>
> > IOW, it's a type constructor of kind (* -> * -> *), like (->) or Either.
> > (* is the kind of types [Int, Char, Either Bool (), Double -> Rational ->
> > Int, ...]
> >
> > [...]
> >
> >> but ghci complains:
> >> board.hs:34:15:
> >> Kind mis-match
> >> Expected kind `* -> * -> *', but `pos -> Maybe piece' has kind `*'
> >> In the instance declaration for `Board (pos
> >> -> Maybe piece) pos piece'
> >
> > Yes, as said above.
> > (pos -> Maybe piece) is a *type*, but the type class expects a type
> > constructor of kind (* -> * ->*) here.
>
> I thought "(pos -> Maybe piece) pos piece" would provide the 3 type
> arguments to Board.
>
> Oh, I see my mistake.  I was seeing "b pos piece" as type parameters for
> Board, but actually Board is just taking a single parameter of kind * ->
> * -> *.

No.

class Board b pos piece where
 -- Update board with piece played at pos
 play :: b pos piece -> pos -> piece -> b pos piece

the class Board takes three parameters: b, pos and piece.

The (first) argument of play is the type (kind *)

b pos piece

Thus b is a type constructor taking two arguments. Since the arguments it 
takes, pos and 
piece, appear as the types of the second and third argument of play, these two 
must be 
plain types (kind *).

Thus

b :: * -> * -> *

But in your instance declaration, in the position of b, you pass

(pos -> Maybe piece), which is a type (kind *) and not a binary type 
constructor as 
required by the class declaration.
If Haskell had type-level lambdas, what you would have needed to pass there is

(/\ t1 t2. (t1 -> Maybe t2))

(or, if Haskell had type-constructor composition: ((. Maybe) . (->)) )

However, Haskell has neither type-level lambdas nor type-constructor 
composition, so you 
can't.
You can only emulate that by using newtypes, hence Method 1 in my reply.

>
> > Method 2: Multiparameter type class with functional dependencies and
> > suitable kinds
> >
> > class Board b pos piece | b -> pos, b -> piece where
> > play :: b -> pos -> piece -> b
> > at :: b -> pos -> Maybe piece
> > empty :: b
> >
> > instance (Eq pos) => Board (pos -> Maybe piece) pos piece where
> > play b pos piece = \p -> if p == pos then Just piece else b p
> > at = id
> > empty = const Nothing
> >
> > requires {-# LANGUAGE FlexibleInstances #-}
> >
> > Not necessarily ideal either.
>
> OK, but that's pretty much precisely what I was aiming for.   I'm not
> sure I understand what the difference between
>
> play :: b pos piece -> pos -> piece -> b pos piece
>
> and
>
> play :: b -> pos -> piece -> b
>
> is.  Does adding type params to b here change its kind?

That's not quite correctly expressed, but basically, yes, that's it.

Any type expression that may legally appear to the left or right of '->' in a 
type 
signature has kind *.

A type expression that takes parameters has a different kind, if it takes one 
plain type 
to produce a plain type, it has kind (* -> *), examples: [], Maybe.
If it takes two plain types to produce a plain type, it has kind (* -> * -> *), 
examples: 
Either, (->).

A type expression may also take type expressions which are not plain types to 
produce a 
plain type, for example StateT. That takes 
1) the state type s (kind *)
2) the transforming (or transformed, I'm not sure about the terminology) Monad 
m 
(kind * -> *)
3) the result type a (kind *)

to produce the plain type

StateT s m a (kind *),

hence StateT :: * -> (* -> *) -> * -> *.

So with the signature

play :: b -> pos -> piece -> b,

b must be a plain type (elementary, like Int, Bool; or a fully applied type 
constructor of 
arity > 0, like [()], Maybe Char, Either Int Bool, ((Int,Int) -> Maybe String) 
or 
StateT [Int] Maybe Bool), that is, a type expression of kind *.

With the signature

play :: b pos piece -> pos -> piece -> b pos piece,

b must be a type expression of arity 2, taking two plain types as arguments, 
that is, a 
type constructor of kind (* -> * -> *), like Either, State, (->) or a partially 
applied 
type constructor of higher arity like ((,,,) Int (Char ->Bool)) [the quadruple 
constructor 
(,,,) of kind (* -> * -> * -> * -> *) applied to two types, leaving two slots 
open].

>
> > Method 3: Associated type families
> >

Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Casey Hawthorne
Please check out Paul Hudak's page.

http://cs-www.cs.yale.edu/homes/hudak-paul/


On Tue, 01 Dec 2009 17:01:29 -0800, you wrote:

>Perhaps someone could either (1) help me do what I'm trying to do, or (2) show 
>me a better way.
>
>I have a problem that is very state-ful and I keep thinking of it as OO, which 
>is driving me crazy. Haskell is several times harder to use than Python in 
>this 
>instance, probably because I'm doing it wrong.
>
>To give you a larger context, this problem is essentially compiling a 
>description of music (my own) into a kind of music-machine-language (CSound). 
>CSound is relatively untidy.
>
>In this one example, in a OO way of thinking, I have data called 
>AssignedNumbers 
>that assigns integers to unique strings and keeps track of the used integers 
>and 
>next available integer (the choice of available integer could follow a number 
>of 
>conventions so I wanted to hide that in an ADT.) So it has an associated 
>function:
>
>getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)
>
>What getNumber does is:
>
>   - check if the string already has a number assigned to it. If so, return 
> that 
>number.
>
>   - if not, pick the next available number.
>
>   - in all cases, return the possibly changed state of AssignedNumbers
>
>Then in a larger data structure, it contains fields of type AssignedNumbers. 
>Like
>
>data MusicStuff = MusicStuff
>   { oscillatorNumbers :: AssignedNumbers
>   , tableNumbers :: AssignedNumbers
>   , ... }
>
>I'm using MusicStuff in a State monad, so I might write a function like
>
>doSomeMusicStuff :: String -> String -> State MusicStuff (Int,Int)
>doSomeMusicStuff aString1 aString2 = do
>ms <- get
>(o1,newOscNums) = getNumber aString1 (oscillatorNumbers ms)
>(t1,newTabNums) = getNumber aString2 (tableNumbers ms)
>put ms { oscillatorNumbers = newOscNums
>   , tableNumbers = newTabNums }
>return (o1,t1)
>
>For what it does, this is extremely verbose and filled with distracting visual 
>content. And this is just a very simple example---my real problem is several 
>times more state-ful. Is there a better way?
>
>Note that in Python it would be a method
>
>def doMusicStuff( self, s1, s2 ) :
>return (self.oscillatorNumbers.next(s1), self.oscillatorNumbers.next(s2))
>
>
>
>
>
>
>___
>Haskell-Cafe mailing list
>Haskell-Cafe@haskell.org
>http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Regards,
Casey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] university courses on type families/GADTs?

2009-12-01 Thread Christopher Anand
I think these topics have been covered in

http://www.cas.mcmaster.ca/~kahl/FP/2009/

Christopher

On Tue, 1 Dec 2009 22:38:14 +0100 (CET)
 Tom Schrijvers  wrote:
> Hello Haskell Cafe,
> 
> I was wondering whether there are any universities that teach about
> Haskell type families or GADTs?
> 
> Thanks,
> 
> Tom
> 
> --
> Tom Schrijvers
> 
> Department of Computer Science
> K.U. Leuven
> Celestijnenlaan 200A
> B-3001 Heverlee
> Belgium
> 
> tel: +32 16 327544
> e-mail: tom.schrijv...@cs.kuleuven.be
> url: http://www.cs.kuleuven.be/~toms/
> 
> Disclaimer: http://www.kuleuven.be/cwis/email_disclaimer.htm
> ___
> 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] seems like I'm on the wrong track

2009-12-01 Thread Michael P Mossey
Perhaps someone could either (1) help me do what I'm trying to do, or (2) show 
me a better way.


I have a problem that is very state-ful and I keep thinking of it as OO, which 
is driving me crazy. Haskell is several times harder to use than Python in this 
instance, probably because I'm doing it wrong.


To give you a larger context, this problem is essentially compiling a 
description of music (my own) into a kind of music-machine-language (CSound). 
CSound is relatively untidy.


In this one example, in a OO way of thinking, I have data called AssignedNumbers 
that assigns integers to unique strings and keeps track of the used integers and 
next available integer (the choice of available integer could follow a number of 
conventions so I wanted to hide that in an ADT.) So it has an associated function:


getNumber :: String -> AssignedNumbers -> (Int,AssignedNumbers)

What getNumber does is:

  - check if the string already has a number assigned to it. If so, return that 
number.


  - if not, pick the next available number.

  - in all cases, return the possibly changed state of AssignedNumbers

Then in a larger data structure, it contains fields of type AssignedNumbers. 
Like

data MusicStuff = MusicStuff
  { oscillatorNumbers :: AssignedNumbers
  , tableNumbers :: AssignedNumbers
  , ... }

I'm using MusicStuff in a State monad, so I might write a function like

doSomeMusicStuff :: String -> String -> State MusicStuff (Int,Int)
doSomeMusicStuff aString1 aString2 = do
   ms <- get
   (o1,newOscNums) = getNumber aString1 (oscillatorNumbers ms)
   (t1,newTabNums) = getNumber aString2 (tableNumbers ms)
   put ms { oscillatorNumbers = newOscNums
  , tableNumbers = newTabNums }
   return (o1,t1)

For what it does, this is extremely verbose and filled with distracting visual 
content. And this is just a very simple example---my real problem is several 
times more state-ful. Is there a better way?


Note that in Python it would be a method

def doMusicStuff( self, s1, s2 ) :
   return (self.oscillatorNumbers.next(s1), self.oscillatorNumbers.next(s2))






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


Re: [Haskell-cafe] Existencial Types

2009-12-01 Thread Luke Palmer
On Tue, Dec 1, 2009 at 4:21 PM, rodrigo.bonifacio
 wrote:
> Thanks Luke.
>
> In fact I, will have different implementations of the Transformation type.
> Something like:
>
> data SelectScenarios = SelectScenarios {
>
> scIds :: [Id]
>
> }

What is this different type buying you?  You can never "downcast" to it later.

> And then I should be able to make SelectScenarios a kind of Transformation.
> So I think that I really need a class. What do you think about it?
>
> instance Transformation SelectScenario where
>
> (<+>)  

So instead of making a type and an instance, just implement it
directly as a Transformation:

selectScenario :: [Id] -> Transformation
selectScenario ids = Transformation {
(<+>) =  {- whatever implementation you gave for (<+>) above, using ids -}
  }

If the only purpose of SelectScenario (your type) is to be used
polymorphically as a Transformation, then this approach is isomorphic
-- i.e. anything you can do with the existential type trick you can do
with this approach.

If SelectScecario is used for other purposes, then give an explicit
cast function

toTransformation :: SelectScenario -> Transformation
toTransformation (SelectScenario ids) = Transformation {
(<+>) = {- implementation of (<+>) just as if it were a class method -}
  }

Existential types only buy you power when the quantified variable
appears more than once on the right hand side, for example:  forall a.
Num a => (a,a).  But even those can usually be factored out into more
direct representations (I seem to recall Oleg has a proof that they
always can, actually).

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


Re: [Haskell-cafe] Existencial Types

2009-12-01 Thread Ryan Ingram
newtype Transformation = Transformation {
(<+>) :: SPLModel -> InstanceModel -> InstanceModel
  }

data SelectScenarios = SelectScenarios { scIds :: [Id] }

scenarioTransform scenario = Transformation $ \spl inst -> something

testScenario = SelectScenarios []
test = scenarioTransform testScenario <+> undefined

Don't use typeclasses unless you really need to.  Higher-order
functions are usually what you want.

  -- ryan

On Tue, Dec 1, 2009 at 3:21 PM, rodrigo.bonifacio
 wrote:
> Thanks Luke.
>
> In fact I, will have different implementations of the Transformation type.
> Something like:
>
> data SelectScenarios = SelectScenarios {
>
> scIds :: [Id]
>
> }
>
>
>
> And then I should be able to make SelectScenarios a kind of Transformation.
> So I think that I really need a class. What do you think about it?
>
> instance Transformation SelectScenario where
>
> (<+>)  
>
>
>
> Regards,
>
> Rodrigo.
>
>
>
>
>
>
>
>
>
>
>
> Em 01/12/2009 19:39, Luke Palmer < lrpal...@gmail.com > escreveu:
>
> On Tue, Dec 1, 2009 at 11:21 AM, David Menendez wrote:
>> On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio
>> wrote:
>>> Dear all, I wrote the following  types:
>>>
 class Transformation t where
  (<+>) :: t -> SPLModel  -> InstanceModel -> InstanceModel
>>>
 data Configuration = forall t . Transformation t => Configuration
 (FeatureExpression, [t])
 type ConfigurationKnowledge = [Configuration]
>
> I would suggest doing away with the class in a case like this.
>
> data Transformation = Transformation {
> (<+>) :: SPLModel -> InstanceModel -> InstanceModel
> }
>
> data Configuration = Configuration FeatureExpression [Transformation]
>
> I suspect that it was OO heritage that l ed you to want a class here?
> Forget that! :-)
>
> Luke
>
>
> ___
> 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] Trying to sort out multiparameter type classes and their instances

2009-12-01 Thread Jeremy Fitzhardinge
On 12/01/09 15:12, Daniel Fischer wrote:
> Am Dienstag 01 Dezember 2009 23:34:46 schrieb Jeremy Fitzhardinge:
>   
>> I'm playing around with some types to represent a game board (like Go,
>> Chess, Scrabble, etc).
>>
>> I'm using a type class to represent the basic Board interface, so I can
>> change the implementation freely:
>>
>> class Board b pos piece where
>> -- Update board with piece played at pos
>> play :: b pos piece -> pos -> piece -> b pos piece
>> 
> So the parameter b of the class is a type constructor taking two types and 
> constructing a 
> type from those.
>   

Yep.

> IOW, it's a type constructor of kind (* -> * -> *), like (->) or Either.
> (* is the kind of types [Int, Char, Either Bool (), Double -> Rational -> 
> Int, ...]
>
> [...]
>   
>> but ghci complains:
>> board.hs:34:15:
>> Kind mis-match
>> Expected kind `* -> * -> *', but `pos -> Maybe piece' has kind `*'
>> In the instance declaration for `Board (pos
>> -> Maybe piece) pos piece'
>>
>> 
> Yes, as said above.
> (pos -> Maybe piece) is a *type*, but the type class expects a type 
> constructor of kind 
> (* -> * ->*) here.
>   

I thought "(pos -> Maybe piece) pos piece" would provide the 3 type
arguments to Board.

Oh, I see my mistake.  I was seeing "b pos piece" as type parameters for
Board, but actually Board is just taking a single parameter of kind * ->
* -> *.

> Method 2: Multiparameter type class with functional dependencies and suitable 
> kinds
>
> class Board b pos piece | b -> pos, b -> piece where
> play :: b -> pos -> piece -> b
> at :: b -> pos -> Maybe piece
> empty :: b
>
> instance (Eq pos) => Board (pos -> Maybe piece) pos piece where
> play b pos piece = \p -> if p == pos then Just piece else b p
> at = id
> empty = const Nothing
>
> requires {-# LANGUAGE FlexibleInstances #-}
>
> Not necessarily ideal either.
>   

OK, but that's pretty much precisely what I was aiming for.   I'm not
sure I understand what the difference between

play :: b pos piece -> pos -> piece -> b pos piece

and

play :: b -> pos -> piece -> b

is.  Does adding type params to b here change its kind?

> Method 3: Associated type families
>
> {-# LANGUAGE TypeFamilies, FlexibleInstances #-}
> module Board where
>
> class Board b where
> type Pos b :: *
> type Piece b :: *
> play :: b -> Pos b -> Piece b -> b
> at :: b -> Pos b -> Maybe (Piece b)
> empty :: b
>
> instance (Eq pos) => Board (pos -> Maybe piece) where
> type Pos (pos -> Maybe piece) = pos
> type Piece (pos -> Maybe piece) = piece
> play b pos piece = \p -> if p == pos then Just piece else b p
> at b p = b p
> empty _ = Nothing
>
> I would try that first.
>   

OK, there's some new stuff there I'm going to have to digest...

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


Re: [Haskell-cafe] Re: ANNOUNCE: Clutterhs 0.1

2009-12-01 Thread Iavor Diatchki
Hi

On Tue, Dec 1, 2009 at 11:02 AM, Gour  wrote:
> Iavor> In general, I don't think that having two similar libraries is a
> Iavor> huge problem.  I tend to do this kind of hacking for fun, and I
> Iavor> really do not enjoy the competition that is being encouraged
> Iavor> when we try to select "the one true library" (e.g., with efforts
> Iavor> such as the Haskell platform).  Let a thousand flowers bloom, I
> Iavor> say :-)
>
> I do not object of having choice - that's why I like Linux, but, otoh,
> prefer to have one fully-baked lib than several half-baked solutions
> which was/is problem with some Haskell packages.

We are baking ;)

> btw, are you interested in binding nbtk/mx toolkit for Moblin which is
> based on Clutter?

I am not that familiar with it, but it might be interesting to have
some Clutter based widgets for GUIs.

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


Re: [Haskell-cafe] Re: inversion lists

2009-12-01 Thread Daniel Fischer
Am Dienstag 01 Dezember 2009 23:31:10 schrieb Ted Zlatanov:
> On Fri, 20 Nov 2009 15:30:49 -0600 Ted Zlatanov  wrote:
>
> TZ> A nice property of inversion lists is that inverting them simply
> TZ> requires removing or adding the minimum possible value at the beginning
> TZ> of the list.  A membership test requires traversal but since the list
> is TZ> sorted we know when to stop if it doesn't exist.  Set union and TZ>
> difference are pretty tricky but at least can stop early if one of two TZ>
> sets is finite.  As I learn more Haskell I'll try implementing these TZ>
> step by step.  Is there any interest in making this an actual module or TZ>
> is it not very useful in the context of Haskell?
>
> OK, here's my current state.  The first two functions are not mine, of
> course (the original invlist' was called h, that's all).
>
> invlist_negate just appends 0 or removes it.  I think the first
> condition (on an empty list) is not necessary.  Should I keep it for
> clarity?

I don't think it's necessary.
As Sjoerd mentioned, the use of 0 is problematic.

>
> For invlist_member I basically pass the current state down into the
> recursion chain on invlist_member'.  The function will end early if it
> can, or it will scan all the way down the list in the worst case (when
> the goal value is greater than the last interval marker).  I think I
> could do it with a foldl but I wasn't able to figure it out.
>
> Any suggestions are welcome.  I can definitely reimplement the invlist
> function similarly to invlist_member, by passing an exclusion state
> boolean down, which will make the code longer.  I'm not sure if it will
> be bad for performance.  I think it will be better because I'll be able
> to do it lazily as opposed to the foldr below which needs a finite list.

No, quite the opposite. foldr is wonderful for lazy list processing.
I just need to make my function a wee bit lazier:

Prelude> let h x zs = x:case zs of { (y:ys) | x+1 == y -> ys; _ -> (x+1):zs; }
Prelude> let invlist xs = foldr h [] xs
Prelude> invlist [1,2,3,7,8,12,13,14,20]
[1,4,7,9,12,15,20,21]
Prelude> take 10 $ invlist [2,5 .. ]
[2,3,5,6,8,9,11,12,14,15]
Prelude> take 10 $ invlist [2,4 .. ]
[2,3,4,5,6,7,8,9,10,11]
Prelude> take 10 $ invlist [2 .. ]
[2^CInterrupted.
Prelude> take 10 $ invlist [2 :: Data.Int.Int16 .. ]
[2,-32768]
-- That's a problem here

Hadn't thought about infinite (or even long) lists when I wrote it.

> Can I do it with a direct foldl instead?

No, foldl cannot produce anything before the whole list has been traversed, so 
it can't 
deal with infinite lists at all.

> I need to look at it
> carefully but maybe someone has a suggestion.
>
> I plan to do set operations after I get the basics right :)
>
> This should really have been in comp.lang.haskell.beginner.  Sorry for
> the elementary stuff, I'm keeping the thread in c.l.h.cafe only to avoid
> double postings at this point.
>
> Thanks
> Ted
>
> invlist' :: Num a => a -> [a] -> [a]
> invlist' x (y:ys)
>
>  | x+1 == y = x:ys
>
> invlist' x zs = x:(x+1):zs

invlist' :: Integral a => a -> [a] -> [a]
invlist' x zs = x:ws
where
  ws = case zs of
  (y:ys) | x+1 == y -> ys
  _ -> (x+1):zs

-- we could use Num here, but for an implementation of sets via inversion lists,
-- Integral is the appropriate setting. Perhaps even better use Integral and 
Bounded

invlist' :: (Integral a, Bounded a) => a -> [a] -> [a]
invlist' x _
| x == maxBound = [x]
invlist' x zs = x:ws
where
  ws = case zs of
  (y:ys) | x+1 == y -> ys
  _ -> (x+1):zs


Now:
Prelude> invlist [2 :: Data.Int.Int8 .. ]
[2]

:D
>
Don't forget a type signature here. Otherwise you'll get bitten by the 
monomorphism 
restriction.
invlist :: (Integral a, Bounded a) => [a] -> [a]
> invlist = foldr invlist' []
>

Problem. That is only sensible if we only consider sets of nonnegative numbers.
For Integral and Bounded,

invlist_negate (x:xs)
| x == minBound = xs
invlist_negate xs = minBound:xs

> invlist_negate [] = [0]
> invlist_negate (0:xs) = xs
> invlist_negate xs = 0:xs
>
> invlist_member _ [] = False
>
> -- bootstrap membership test with a False exclusion state (an inversion
> list begins with the first included value) invlist_member goal (x:xs) =
> invlist_member' goal False (x:xs)
>
> invlist_member' goal exclude (x:xs) =
> if goal < x then
>exclude
> else
> invlist_member' goal (not exclude) xs -- flip the exclusion state
> of the list
>
> invlist_member' _ exclude _ = exclude   -- if we can't match one more
> element, return the current exclusion state

invlist_member :: (Integral a, Bounded a) => a -> [a] -> Bool
invlist_member goal = foldr (\n b -> if goal < n then False else not b) False

*maybe* I'll think about unions, intersections and other set operations as 
foldr's.

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

Re: [Haskell-cafe] Re: inversion lists

2009-12-01 Thread Daniel Peebles
You probably don't want that minBound in the pattern, but rather as a
comparison in a guard.

Dan

On Tue, Dec 1, 2009 at 6:14 PM, Sjoerd Visscher  wrote:
> Hi Ted,
>
> Some tips:
>> invlist_negate [] = [0]
>> invlist_negate (0:xs) = xs
>> invlist_negate xs = 0:xs
>
> You are doing this for generic Num instances, so 0 probably isn't the lower 
> bound. Haskell has another type class for this: Bounded. Then you can use 
> minBound instead of 0. Also the first line is just a special case of the last 
> one.
>
> invlist_negate :: (Bounded a, Num a) => [a] -> [a]
> invlist_negate (minBound : xs) = xs
> invlist_negate xs = minBound : xs
>
> Try doing invlist_member together with a function invlist_notMember (just 
> like there is notElem for lists), I think that would clean things up a bit.
>
> Keep on going, there's lots of fun ahead!
>
> greetings,
> Sjoerd
>
> --
> Sjoerd Visscher
> sjo...@w3future.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] Existencial Types

2009-12-01 Thread rodrigo.bonifacio
Thanks Luke.
In fact I, will have different implementations of the Transformation type. Something like:
data SelectScenarios = SelectScenarios {
scIds :: [Id]
}
 
And then I should be able to make SelectScenarios a kind of Transformation. So I think that I really need a class. What do you think about it?
instance Transformation SelectScenario where
(<+>)  
 
Regards,
Rodrigo.
 
 
 
 
 
Em 01/12/2009 19:39, Luke Palmer < lrpal...@gmail.com > escreveu:
On Tue, Dec 1, 2009 at 11:21 AM, David Menendez  wrote:> On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio>  wrote:>> Dear all, I wrote the following  types:> class Transformation t where>>>  (<+>) :: t -> SPLModel  -> InstanceModel -> InstanceModel> data Configuration = forall t . Transformation t => Configuration>>> (FeatureExpression, [t])>>> type ConfigurationKnowledge = [Configuration]I would suggest doing away with the class in a case like this.data Transformation = Transformation { (<+>) :: SPLModel -> InstanceModel -> InstanceModel }data Configuration = Configuration FeatureExpression [Transformation]I suspect that it was OO heritage that l
 ed you to want a class here?Forget that!  :-)Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: inversion lists

2009-12-01 Thread Sjoerd Visscher
Hi Ted,

Some tips:
> invlist_negate [] = [0]
> invlist_negate (0:xs) = xs
> invlist_negate xs = 0:xs

You are doing this for generic Num instances, so 0 probably isn't the lower 
bound. Haskell has another type class for this: Bounded. Then you can use 
minBound instead of 0. Also the first line is just a special case of the last 
one.

invlist_negate :: (Bounded a, Num a) => [a] -> [a]
invlist_negate (minBound : xs) = xs
invlist_negate xs = minBound : xs

Try doing invlist_member together with a function invlist_notMember (just like 
there is notElem for lists), I think that would clean things up a bit.

Keep on going, there's lots of fun ahead!

greetings,
Sjoerd

--
Sjoerd Visscher
sjo...@w3future.com



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


Re: [Haskell-cafe] Trying to sort out multiparameter type classes and their instances

2009-12-01 Thread Daniel Fischer
Am Dienstag 01 Dezember 2009 23:34:46 schrieb Jeremy Fitzhardinge:
> I'm playing around with some types to represent a game board (like Go,
> Chess, Scrabble, etc).
>
> I'm using a type class to represent the basic Board interface, so I can
> change the implementation freely:
>
> class Board b pos piece where
> -- Update board with piece played at pos
> play :: b pos piece -> pos -> piece -> b pos piece

So the parameter b of the class is a type constructor taking two types and 
constructing a 
type from those.
IOW, it's a type constructor of kind (* -> * -> *), like (->) or Either.
(* is the kind of types [Int, Char, Either Bool (), Double -> Rational -> Int, 
...]

> -- Query pos to get piece (Nothing if off board)
> at :: b pos piece -> pos -> Maybe piece
> -- Empty board
> empty :: b pos piece
>
> and a Position on the board is represented thus:
>
> class Position p where
> up :: p -> p
> down :: p -> p
> left :: p -> p
> right :: p -> p
>
> With a concrete implementation using a tuple:
>
> instance (Enum c,Enum r) => Position (c,r) where
> up = second pred
> down = second succ
> left = first pred
> right = first succ
>
>
> My initial Board is a function: position -> Maybe piece, but I'm having
> a hard time writing the instance for it.  My first attempt is:
>
> instance Board (pos -> Maybe piece) pos piece where
> empty = \_ -> Nothing
> at = ($)
> play b pos piece = move
> where move pos' | pos' == pos = Just piece
>
> | otherwise   = b pos'
>
> but ghci complains:
> board.hs:34:15:
> Kind mis-match
> Expected kind `* -> * -> *', but `pos -> Maybe piece' has kind `*'
> In the instance declaration for `Board (pos
> -> Maybe piece) pos piece'
>

Yes, as said above.
(pos -> Maybe piece) is a *type*, but the type class expects a type constructor 
of kind 
(* -> * ->*) here.

>
> Playing around with parentheses on the instance line got various similar
> messages, but I couldn't get anything to work.
>
> What am I missing here?
>
> One thing that strikes me is that "Board (pos -> Maybe piece) pos piece"
> has a lot of redundancy, and I'm wondering if I'm defining the Board
> type class wrong in the first place.
>
> Given that the "b" type parameter necessarily defines the position and
> pieces, I tried using dependent types:
>
> class Board b | b -> pos, b -> piece where ...

Method 1: The class above, with a modified instance.

newtype Brd pos piec = Brd { mpiece :: pos -> Maybe piece }

instance (Eq pos) => Board Brd pos piece where
play b pos piece = Brd $ \p -> if p == pos then Just piece else mpiece b pos
...

Perhaps not truly satisfying.

Method 2: Multiparameter type class with functional dependencies and suitable 
kinds

class Board b pos piece | b -> pos, b -> piece where
play :: b -> pos -> piece -> b
at :: b -> pos -> Maybe piece
empty :: b

instance (Eq pos) => Board (pos -> Maybe piece) pos piece where
play b pos piece = \p -> if p == pos then Just piece else b p
at = id
empty = const Nothing

requires {-# LANGUAGE FlexibleInstances #-}

Not necessarily ideal either.

Method 3: Associated type families

{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
module Board where

class Board b where
type Pos b :: *
type Piece b :: *
play :: b -> Pos b -> Piece b -> b
at :: b -> Pos b -> Maybe (Piece b)
empty :: b

instance (Eq pos) => Board (pos -> Maybe piece) where
type Pos (pos -> Maybe piece) = pos
type Piece (pos -> Maybe piece) = piece
play b pos piece = \p -> if p == pos then Just piece else b p
at b p = b p
empty _ = Nothing

I would try that first.
Choose your pick.


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


[Haskell-cafe] Re: [Haskell] ANN: NoSlow - Microbenchmarks for array libraries

2009-12-01 Thread Henning Thielemann


On Fri, 27 Nov 2009, Henning Thielemann wrote:


On Fri, 27 Nov 2009, Roman Leshchinskiy wrote:


You can get more information (including the ugly tables) from my blog

 http://unlines.wordpress.com/2009/11/27/noslow


Btw. storablevector supports 'zip' using
http://hackage.haskell.org/package/storable-tuple
 but you may also use 'zipWith' with an atomar result type for testing.


However, I have noticed that the instances in storable-tuple are not quite 
efficient. They are implemented with storable-record, which is elegant, 
but apparently too hard to compile efficiently for GHC. Storable-record 
computes the offsets for members of a record automatically according to 
their aligment constraints. But GHC seems not to realize, that the offsets 
are constants.

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


[Haskell-cafe] Trying to sort out multiparameter type classes and their instances

2009-12-01 Thread Jeremy Fitzhardinge
I'm playing around with some types to represent a game board (like Go,
Chess, Scrabble, etc).

I'm using a type class to represent the basic Board interface, so I can
change the implementation freely:

class Board b pos piece where
-- Update board with piece played at pos
play :: b pos piece -> pos -> piece -> b pos piece
-- Query pos to get piece (Nothing if off board)
at :: b pos piece -> pos -> Maybe piece
-- Empty board
empty :: b pos piece

and a Position on the board is represented thus:

class Position p where
up :: p -> p
down :: p -> p
left :: p -> p
right :: p -> p

With a concrete implementation using a tuple:

instance (Enum c,Enum r) => Position (c,r) where
up = second pred
down = second succ
left = first pred
right = first succ


My initial Board is a function: position -> Maybe piece, but I'm having
a hard time writing the instance for it.  My first attempt is:

instance Board (pos -> Maybe piece) pos piece where
empty = \_ -> Nothing
at = ($)
play b pos piece = move
where move pos' | pos' == pos = Just piece
| otherwise   = b pos'

but ghci complains:
board.hs:34:15:
Kind mis-match
Expected kind `* -> * -> *', but `pos -> Maybe piece' has kind `*'
In the instance declaration for `Board (pos
-> Maybe piece) pos piece'


Playing around with parentheses on the instance line got various similar
messages, but I couldn't get anything to work.

What am I missing here?

One thing that strikes me is that "Board (pos -> Maybe piece) pos piece"
has a lot of redundancy, and I'm wondering if I'm defining the Board
type class wrong in the first place.

Given that the "b" type parameter necessarily defines the position and
pieces, I tried using dependent types:

class Board b | b -> pos, b -> piece where ...

but this complains "Not in scope: type variable `pos'/`piece'", so I
tried sprinkling some existential types around as well:

class (forall pos piece. b pos piece) => Board b | b -> pos, b -> piece where 
...

(with and without the dependent types) but this just complains
"malformed class assertion".

As you can probably tell, I'm just thrashing around trying things
without really understanding what's going on here, so I'm hoping someone
can give me some useful pointers.

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


Re: [Haskell-cafe] module export question

2009-12-01 Thread Ross Paterson
On Tue, Dec 01, 2009 at 05:11:42PM -0500, Sean McLaughlin wrote:
> The problem is that I explicitly didn't export 't' as an element of T
> (by not writing T(..)).
> Am I just misunderstanding how exports work?  I couldn't figure out
> what the correct behavior should be by looking at the 98 report.

Exports (and imports) merely enumerate names, not their relationships,
so the original export is equivalent to T(T, t) or T(..).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: inversion lists

2009-12-01 Thread Ted Zlatanov
On Fri, 20 Nov 2009 15:30:49 -0600 Ted Zlatanov  wrote: 

TZ> A nice property of inversion lists is that inverting them simply
TZ> requires removing or adding the minimum possible value at the beginning
TZ> of the list.  A membership test requires traversal but since the list is
TZ> sorted we know when to stop if it doesn't exist.  Set union and
TZ> difference are pretty tricky but at least can stop early if one of two
TZ> sets is finite.  As I learn more Haskell I'll try implementing these
TZ> step by step.  Is there any interest in making this an actual module or
TZ> is it not very useful in the context of Haskell?

OK, here's my current state.  The first two functions are not mine, of
course (the original invlist' was called h, that's all).

invlist_negate just appends 0 or removes it.  I think the first
condition (on an empty list) is not necessary.  Should I keep it for
clarity?

For invlist_member I basically pass the current state down into the
recursion chain on invlist_member'.  The function will end early if it
can, or it will scan all the way down the list in the worst case (when
the goal value is greater than the last interval marker).  I think I
could do it with a foldl but I wasn't able to figure it out.

Any suggestions are welcome.  I can definitely reimplement the invlist
function similarly to invlist_member, by passing an exclusion state
boolean down, which will make the code longer.  I'm not sure if it will
be bad for performance.  I think it will be better because I'll be able
to do it lazily as opposed to the foldr below which needs a finite list.
Can I do it with a direct foldl instead?  I need to look at it
carefully but maybe someone has a suggestion.

I plan to do set operations after I get the basics right :)

This should really have been in comp.lang.haskell.beginner.  Sorry for
the elementary stuff, I'm keeping the thread in c.l.h.cafe only to avoid
double postings at this point.

Thanks
Ted

invlist' :: Num a => a -> [a] -> [a]
invlist' x (y:ys)
 | x+1 == y = x:ys
invlist' x zs = x:(x+1):zs

invlist = foldr invlist' []

invlist_negate [] = [0]
invlist_negate (0:xs) = xs
invlist_negate xs = 0:xs

invlist_member _ [] = False

-- bootstrap membership test with a False exclusion state (an inversion list 
begins with the first included value)
invlist_member goal (x:xs) = invlist_member' goal False (x:xs)

invlist_member' goal exclude (x:xs) = 
if goal < x then
   exclude
else
invlist_member' goal (not exclude) xs -- flip the exclusion state of 
the list

invlist_member' _ exclude _ = exclude   -- if we can't match one more 
element, return the current exclusion state

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


Re: [Haskell-cafe] module export question

2009-12-01 Thread Ross Mellgren

It looks like it is specified and the intended behavior:

From the report, section 5.2:

An algebraic datatype T declared by a data or newtype declaration may  
be named in one of three ways:
The form T names the type but not the constructors or field names. The  
ability to export a type without its constructors allows the  
construction of abstract datatypes (see Section 5.8).
The form T(c1,...,cn), names the type and some or all of its  
constructors and field names.
The abbreviated form T(..) names the type and all its constructors and  
field names that are currently in scope (whether qualified or not).


And then later similarly for imports from 5.3.1:

Exactly which entities are to be imported can be specified in one of  
the following three ways:


The imported entities can be specified explicitly by listing them in  
parentheses. Items in the list have the same form as those in export  
lists, except qualifiers are not permitted and the `module modid'  
entity is not permitted. When the(..) form of import is used for a  
type or class, the (..) refers to all of the constructors, methods, or  
field names exported from the module.
The list must name only entities exported by the imported module. The  
list may be empty, in which case nothing except the instances is  
imported.




-Ross

On Dec 1, 2009, at 5:18 PM, Luke Palmer wrote:

On Tue, Dec 1, 2009 at 3:11 PM, Sean McLaughlin   
wrote:

Say I have the following module:


module A
 ( T(T)
 , t
 , val
 )
where

data T = T { t :: Int }

val :: T
val = T 7



When I use A with the following imports, I don't expect this to work,
but it does:

import qualified A
import A(T(..))

main = putStrLn $ show $ t A.val

The problem is that I explicitly didn't export 't' as an element of T
(by not writing T(..)).
Am I just misunderstanding how exports work?  I couldn't figure out
what the correct
behavior should be by looking at the 98 report.


Oh interesting.  What a crazy corner case.  I also feel like your
program shouldn't be valid.  Maybe it's a bug?
___
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] module export question

2009-12-01 Thread Luke Palmer
On Tue, Dec 1, 2009 at 3:11 PM, Sean McLaughlin  wrote:
> Say I have the following module:
>
> 
> module A
>  ( T(T)
>  , t
>  , val
>  )
> where
>
> data T = T { t :: Int }
>
> val :: T
> val = T 7
> 
>
>
> When I use A with the following imports, I don't expect this to work,
> but it does:
>
> import qualified A
> import A(T(..))
>
> main = putStrLn $ show $ t A.val
>
> The problem is that I explicitly didn't export 't' as an element of T
> (by not writing T(..)).
> Am I just misunderstanding how exports work?  I couldn't figure out
> what the correct
> behavior should be by looking at the 98 report.

Oh interesting.  What a crazy corner case.  I also feel like your
program shouldn't be valid.  Maybe it's a bug?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] module export question

2009-12-01 Thread Sean McLaughlin
Say I have the following module:


module A
  ( T(T)
  , t
  , val
  )
where

data T = T { t :: Int }

val :: T
val = T 7



When I use A with the following imports, I don't expect this to work,
but it does:

import qualified A
import A(T(..))

main = putStrLn $ show $ t A.val

The problem is that I explicitly didn't export 't' as an element of T
(by not writing T(..)).
Am I just misunderstanding how exports work?  I couldn't figure out
what the correct
behavior should be by looking at the 98 report.

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


Re: [Haskell-cafe] Existencial Types

2009-12-01 Thread Luke Palmer
On Tue, Dec 1, 2009 at 11:21 AM, David Menendez  wrote:
> On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio
>  wrote:
>> Dear all, I wrote the following  types:
>>
>>> class Transformation t where
>>>  (<+>) :: t -> SPLModel  -> InstanceModel -> InstanceModel
>>
>>> data Configuration = forall t . Transformation t => Configuration
>>> (FeatureExpression, [t])
>>> type ConfigurationKnowledge = [Configuration]

I would suggest doing away with the class in a case like this.

data Transformation = Transformation {
(<+>) :: SPLModel -> InstanceModel -> InstanceModel
  }

data Configuration = Configuration FeatureExpression [Transformation]

I suspect that it was OO heritage that led you to want a class here?
Forget that!  :-)

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


[Haskell-cafe] university courses on type families/GADTs?

2009-12-01 Thread Tom Schrijvers

Hello Haskell Cafe,

I was wondering whether there are any universities that teach about 
Haskell type families or GADTs?


Thanks,

Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: tom.schrijv...@cs.kuleuven.be
url: http://www.cs.kuleuven.be/~toms/

Disclaimer: http://www.kuleuven.be/cwis/email_disclaimer.htm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazy logging (was: Are there standard idioms for lazy, pure error handling?)

2009-12-01 Thread Daniel Fischer
Am Dienstag 01 Dezember 2009 21:00:13 schrieb Daniel Fischer:
> Am Dienstag 01 Dezember 2009 20:21:27 schrieb Evan Laforge:
> > This is only peripherally related, but I also have a lot of list
> > functions that can possibly be an error, but usually processing can
> > continue.  So they tend to return [Either Error Result].  I have
> > another function thus:
> >
> > -- A foldr version is not lazy enough and overflows the stack.
>
> try
>
> foldr (\e ~(ls,rs) -> case e of { Left l -> (l:ls,rs); Right r -> (ls,r:rs)
> }) ([],[])
>
> with the lazy pattern, it should be lazy enough.

Yup. Tested now.

>
> > partition_either [] = ([], [])
> > partition_either (x:xs) =
> > let (ls, rs) = partition_either xs
> > in case x of
> > Left l -> (l:ls, rs)
> > Right r -> (ls, r:rs)
> >
> > I was a little surprised I couldn't find this in the standard
> > library... or maybe it is?
>
> Data.Either.partitionEithers

And that's not lazy enough, either.
Ticket: http://hackage.haskell.org/trac/ghc/ticket/3709

>
> Data.List.partition isLeft
>
> isLeft (Left _) = True
> isLeft _ = False

Not quite the same.

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


Re: [Haskell-cafe] lazy logging (was: Are there standard idioms for lazy, pure error handling?)

2009-12-01 Thread Daniel Fischer
Am Dienstag 01 Dezember 2009 20:21:27 schrieb Evan Laforge:
> This is only peripherally related, but I also have a lot of list
> functions that can possibly be an error, but usually processing can
> continue.  So they tend to return [Either Error Result].  I have
> another function thus:
>
> -- A foldr version is not lazy enough and overflows the stack.

try

foldr (\e ~(ls,rs) -> case e of { Left l -> (l:ls,rs); Right r -> (ls,r:rs) }) 
([],[])

with the lazy pattern, it should be lazy enough.

> partition_either [] = ([], [])
> partition_either (x:xs) =
> let (ls, rs) = partition_either xs
> in case x of
> Left l -> (l:ls, rs)
> Right r -> (ls, r:rs)
>
> I was a little surprised I couldn't find this in the standard
> library... or maybe it is?

Data.Either.partitionEithers

Data.List.partition isLeft

isLeft (Left _) = True
isLeft _ = False


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


[Haskell-cafe] lazy logging (was: Are there standard idioms for lazy, pure error handling?)

2009-12-01 Thread Evan Laforge
This is only peripherally related, but I also have a lot of list
functions that can possibly be an error, but usually processing can
continue.  So they tend to return [Either Error Result].  I have
another function thus:

-- A foldr version is not lazy enough and overflows the stack.
partition_either [] = ([], [])
partition_either (x:xs) =
let (ls, rs) = partition_either xs
in case x of
Left l -> (l:ls, rs)
Right r -> (ls, r:rs)

I was a little surprised I couldn't find this in the standard
library... or maybe it is?

Anyway, the trick is logging the errors while incrementally processing
the non-errors.  Logging them first forces the whole thing.  Mixing
the logging in with the processing forces the processing to be in IO
and is not as nice as having it separate.  If the next processing step
is also pure, the errors must be propagated.  'map (fmap f)' should do
it, as long as the errors are all the same type.  It's still not ideal
because the logs happen in a bunch at the end, and are still taking up
memory meanwhile.

The only thing I can think of is the dreaded lazy IO... plain
unsafePerformIO wouldn't work because nothing is forcing it.  It would
be sort of an output version of getContents, but it would have to have
some magic to know when a thunk has been evaluated without forcing it.
 But hey, the debugger does it!  And the RTS already happily logs
things in the middle of pure computation, so this would just be giving
programmers access to it... so it's not *so* crazy :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: Clutterhs 0.1

2009-12-01 Thread Gour
On Tue, 1 Dec 2009 10:06:14 -0800
>> "Iavor" == Iavor Diatchki  wrote:

Iavor> I work with Trevor on the other Clutter binding.  We did
Iavor> exchange a few messages with Matt, but we were not sure how to
Iavor> combine the two libraries because our approaches to writing the
Iavor> binding were a bit different.  

OK.

Iavor> In general, I don't think that having two similar libraries is a
Iavor> huge problem.  I tend to do this kind of hacking for fun, and I
Iavor> really do not enjoy the competition that is being encouraged
Iavor> when we try to select "the one true library" (e.g., with efforts
Iavor> such as the Haskell platform).  Let a thousand flowers bloom, I
Iavor> say :-)

I do not object of having choice - that's why I like Linux, but, otoh,
prefer to have one fully-baked lib than several half-baked solutions
which was/is problem with some Haskell packages.

btw, are you interested in binding nbtk/mx toolkit for Moblin which is
based on Clutter?


Sincerely,
Gour

-- 

Gour  | Hlapicina, Croatia  | GPG key: F96FF5F6

-- 

Gour  | Hlapicina, Croatia  | GPG key: F96FF5F6



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


Re: [Haskell-cafe] Existencial Types

2009-12-01 Thread David Menendez
On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio
 wrote:
> Dear all, I wrote the following  types:
>
>> class Transformation t where
>>  (<+>) :: t -> SPLModel  -> InstanceModel -> InstanceModel
>
>> data Configuration = forall t . Transformation t => Configuration
>> (FeatureExpression, [t])
>> type ConfigurationKnowledge = [Configuration]
>
>
>
> I tried to write a function that retrieves the list of transformations of a
> configuration. Bellow a code snip of such a function.
>
>> transformations ck fc = concat [snd c | (Configuration c) <- ck, eval fc
>> (fst c)]
>
> However, compiling this I got:
>
> ---
> Inferred type is less polymorphic than expected
> Quantified type variable `t' escapes
> When checking an existential match that binds
> c :: (FeatureModel.Types.FeatureExpression, [t])
> The pattern(s) have type(s): Configuration
> The body has type: [t]
> In a stmt of a list comprehension: (Configuration c) <- ck
> In the first argument of `concat', namely
> `[snd c | (Configuration c) <- ck, eval fc (fst c)]'
>
> ---
>
>
>
> How can I fix this problem?

The problem is that transformations is creating a heterogenous list,
i.e., there is no guarantee that the contents of the list all have the
same type.

You can get around this by declaring a type representing any transformation,

data SomeTransformation = forall t. Transformation t => ST t

and having transformation return a list of those.

However, if Transformation really only has one member function, you'd
be better off eliminating the existential types entirely.

e.g.,

data Configuration = Configuration FeatureExpression (SPLModel ->
InstanceModel -> InstanceModel)

-- 
Dave Menendez 

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


Re: [Haskell-cafe] Re: ANNOUNCE: Clutterhs 0.1

2009-12-01 Thread Iavor Diatchki
Hi,
I work with Trevor on the other Clutter binding.  We did exchange a
few messages with Matt, but we were not sure how to combine the two
libraries because our approaches to writing the binding were a bit
different.  In general, I don't think that having two similar
libraries is a huge problem.  I tend to do this kind of hacking for
fun, and I really do not enjoy the competition that is being
encouraged when we try to select "the one true library" (e.g., with
efforts such as the Haskell platform).  Let a thousand flowers bloom,
I say :-)
-Iavor

On Mon, Nov 30, 2009 at 7:12 PM, Matt Arsenault  wrote:
> On Mon, 2009-11-30 at 09:22 +0100, Gour wrote:
>
>> Do you have some public repo for the project's code?
>
> I thought I mentioned this somewhere, but I've been using this git repo:
>
> http://jayne.hortont.com/git/cgit.cgi/clutterhs.git/
>
>
> ___
> 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] Existencial Types

2009-12-01 Thread rodrigo.bonifacio
Dear all, I wrote the following  types:
> class Transformation t where >  (<+>) :: t -> SPLModel  -> InstanceModel -> InstanceModel
> data Configuration = forall t . Transformation t => Configuration (FeatureExpression, [t])> type ConfigurationKnowledge = [Configuration]
 
I tried to write a function that retrieves the list of transformations of a configuration. Bellow a code snip of such a function.
> transformations ck fc = concat [snd c | (Configuration c) <- ck, eval fc (fst c)]
However, compiling this I got:
--- Inferred type is less polymorphic than expected Quantified type variable `t' escapes When checking an existential match that binds c :: (FeatureModel.Types.FeatureExpression, [t]) The pattern(s) have type(s): Configuration The body has type: [t] In a stmt of a list comprehension: (Configuration c) <- ck In the first argument of `concat', namely `[snd c | (Configuration c) <- ck, eval fc (fst c)]'
---
 
How can I fix this problem?
Thanks,
Rodrigo.
 
 
 
 
 
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fwd: Timing and Atom

2009-12-01 Thread Lee Pike

[Tom -- resending my reply---I forgot to post to the list.]

Neil, could you provide a reference (more on the practical side than  
the theory side) for the Stochastic Process Algebras you mention?  And  
is there an embedding in Haskell? :)


Lee


Begin forwarded message:

From: Lee Pike 
Date: November 30, 2009 10:14:33 PM PST
To: Tom Hawkins 
Subject: Re: Timing and Atom

Tom,

Thanks a lot for the detailed reply!


If you need greater timing resolution than what is provided by the
main loop, then I think the only option is to reference a hardware
counter.


Right, of course. Use a hardware counter if you're not using a RTOS.   
That was the quick answer I wasn't considering. :)



I never considered running Atom generated functions in an asynchronous
loop until you posted your "Atomic Fibonacci Server" example


Yeah, I always think it's fun to use synchronous languages  
asynchronously.  Usually people think of trying to implement synchrony  
from asynchronous languages.


But there is a wide field of applications where this approach would  
work just

fine -- not having to worry about meeting a hard loop time would
certainly simplify the design.


I think it's a trade-off, right?  You don't worry as much about time,  
but you have to worry about doing synchronization using handshakes or  
similar protocols.  I know folks who make fault-tolerant systems  
generally prefer synchronized systems since asynchrony gets really  
hard once you start considering the possibility of random faults (See,  
for example,  or _Real-Time  
Systems_ by Hermann Kopetz).


Could some form of static analysis be applied to provide the timing  
guarantees?


Of the asynchronous system (e.g., the "Fib. server")?  In something  
like that, it should function under any possible schedule because of  
the handshakes (I should model-check it to prove that).  Did I  
misunderstand your point?


Thanks again for answering my question!

Lee


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


[Haskell-cafe] KiCS (Curry to Haskell interpreter) problem

2009-12-01 Thread Pasqualino "Titto" Assini
Hi,

I am playing around with KiCS and I have a strange problem, when I
evaluate a goal the variable bindings are not displayed, I see only
the value of the expression.

The same expression evaluated in pakcs (another curry interpreter)
displays the bindings correctly.

Is this a known bug?

I would have contacted the author but his email in not in the haskell
cabal file.

Incidentally, is anyone else using KiCS ?  Any comments/remarks ?

Best,

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


Re: [Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-01 Thread David Menendez
On Tue, Dec 1, 2009 at 5:29 AM, Heinrich Apfelmus
 wrote:
> Duncan Coutts wrote:
>> On Mon, 2009-11-30 at 06:08 +, Malcolm Wallace wrote:
>>> However, if you really want to terminate the stream at
>>> the first error, and to reflect this in the type, then I guess you can
>>> define your own list type:
>>>
>>> data ListThenError e a = Cons a (ListThenError e a)
>>>                         | Error e
>>>
>>> Of course this has the disadvantage that then your consumer must
>>> change to use this type too.
>>
>> I've been using this list type quite a lot recently. It's in the 'tar'
>> package for example. It comes with variants of the standard functions
>> foldl, foldr, unfoldr that take into account the error possibility.
>>
>> At some point we should probably make a package to standardise and
>> document this lazy error handling idiom.
>
> I propose to (trivially) generalize this type to "list with an end"
>
>   data ListEnd a b = Cons a (ListEnd a b)
>                    | End b
>
> because it may have other uses than just lazy error handling.

This is almost a composition of a non-determism monad transformer with
an exception monad.

Specifically, "LogicT (Either e) a" is (almost) isomorphic with

data NX e a = Cons a (NX e a) | Nil | Error e


reflect :: NX e a -> LogicT (Either e) a
reflect (Cons a r) = return a `mplus` reflect r
reflect Nil = mzero
reflect (Error e) = lift (Left e)

reify :: LogicT (Either e) a -> NX e a
reify m = j $ runLogicT m (\a -> Right . Cons a . j) (Right Nil)
where j = either Error id


-- 
Dave Menendez 

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


Re: [Haskell-cafe] Great Programs to Read?

2009-12-01 Thread Michael Lesniak
Hello,

thanks for all the advices; will have enough to read for the next
weeks and months! :-)

- Michael

-- 
Dipl.-Inf. Michael C. Lesniak
University of Kassel
Programming Languages / Methodologies Research Group
Department of Computer Science and Electrical Engineering

Wilhelmshöher Allee 73
34121 Kassel

Phone: +49-(0)561-804-6269
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Great Programs to Read?

2009-12-01 Thread Jason Foutz

I'd suggest the Prelude and Data.List

The code is very clear and thoroughly documented.
Knowing what is there will pay off again and again.


- Jason


On Nov 30, 2009, at 5:22 AM, Michael Lesniak wrote:


Hello,

In terms of

 "to become a great programmer, you need to read great programs"[1]

what are "great" programs written in Haskell (for your personal
definition of great), which source code is freely available on hackage
or somewhere else on the net?

I'm personally also interested in your definitions of great; for me, a
great programs is defined by one of

* good and well-written documentation
 (literate Haskell helps a lot)
* novel ideas to use functional programming
* elegance
* showing how functional programming can ease tasks that
 are difficult to achieve in an imperative style

Maybe we should create a Page on haskell.org (which I would do if I
had write-access) mirroring the pages [2,3]?

Kind regards,
Michael

[1] http://c2.com/cgi/wiki/Wiki?ReadGreatPrograms
[2] http://c2.com/cgi/wiki/Wiki?GreatProgramsToRead
[3] http://c2.com/cgi/wiki/Wiki?ProgramsToRead


--
Dipl.-Inf. Michael C. Lesniak
University of Kassel
Programming Languages / Methodologies Research Group
Department of Computer Science and Electrical Engineering

Wilhelmshöher Allee 73
34121 Kassel

Phone: +49-(0)561-804-6269
___
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] Function composition questions from a newbie

2009-12-01 Thread Daniel Fischer
Am Dienstag 01 Dezember 2009 10:32:24 schrieb newbie2009:
> leledumbo wrote:
> > None of them are legal, at least in my WinHugs they're not. What tools
> > are you using?
>
> 1) I am using GHCi. I put the following into a file named composition.hs
> and typed ":l composition.hs" in GHCi. I also did a ":browse Main"
> 2) Next, I installed WinHugs, and loaded the same hs file. It failed with
> an error when processing the definition for composition2

That's because composition2 has the context (Num (a -> a), Num a), which isn't 
allowed by 
Haskell98 [A type class constraint must have the form (T a1 a2 ... an), where T 
is a type 
constructor of arity n and the ai are *distinct* type variables; so (Num (a -> 
b)) would 
be legal, but (Num (a -> a)) isn't because it uses the same type variable 
twice]. If you 
enable extensions (I don't know how to do it in WinHugs, in hugs you'd pass the 
flag -98 
on the command line: hugs -98 composition.hs) it will work.

ghci has by default a few extensions enabled, so it accepts such a context *if 
it infers 
it itself* - if you want to give such a context in a type signature, you must 
enable 
FlexibleContexts ({-# LANGUAGE FlexibleContexts #-} in the source file or 
-XFlexibleContexts on the command line).

> 3) is GHC the standard Haskell implementation or should i be using WinHugs?

Depends on for what you'll be using it. For any serious programmes, you'll need 
GHC to 
compile. And GHC implements more (seriously useful) extensions. And most code 
will run 
significantly faster in ghci than in hugs/WinHugs.
But hugs/WinHugs loads the code faster.
If you're working on a large project, it can be bothersome to wait for ghci to 
load the 
code again after making changes, so testing the changes in hugs/WinHugs is 
preferred by 
some (I've never worked on a project that took more than a few seconds to load 
in ghci, 
which is more than compensated by the faster execution, so I don't use hugs 
much).

While learning Haskell, it's probably good to use hugs/WinHugs at least 
alongside ghci 
because hugs' error messages are often more newbie-friendly.

>
> ---8<---

What does ghci tell us is the type of things, and why does it tell us that?

>
square :: (Num a) => a -> a
Obvious, isn't it?
> square x = x * x

add :: (Num a) => a -> a -> a 
That too.
> add x y = x + y

add3 :: (Num a) => a -> a -> a -> a   
And that.
> add3 x y z = x + y + z

composition1 :: Integer -> Integer -> Integer 
This - not.
> composition1 = add . square

Why is the type of composition1 not
composition1 :: (Num a) => a -> a -> a
as one would expect from the types of square, add and (.) ?

Welcome to the wonderful world of "The dreaded Monomorphism Restriction".
(http://haskell.org/onlinereport/decls.html#sect4.5.5 , 
http://www.haskell.org/haskellwiki/Monomorphism_restriction )
Indeed, (Num a) => a -> a -> a *is* the type determined by type inference.
But since it is defined with neither type signature nor argument, the 
monomorphism 
restriction says the type variable a must be resolved to a plain type. By the 
defaulting 
rules, the type variable a is replaced by Integer.

To give composition1 the more general type,
a) give a type signature
b) define it with an argument: composition1 x = (add . square) x
c) pass -XNoMonomorphismRestriction to ghci on the command line 
(or put ":set -XNoMonomorphismRestriction" in your .ghci file).

a) is good practice anyway
b) is a good way if you define functions at the interactive prompt
c) is especially good if you don't want to write type signatures

> -- composition1 5 6 == 31
>
> -- composition2 = square . add -- wont work
>
composition2 :: (Num (a -> a), Num a) => a -> a -> a  
Okay, (square . add) x = square (add x) = (add x) * (add x); If x has type a 
(belonging to 
the Num class), add x has type (a -> a), since we want to apply square to that, 
its type 
also must belong to the Num class, hence the inferred type
> composition2 x = (square . add) x -- to make it work, make composition2
> take an argument

Without the argument, we'd enter MR-land again, but now the constraint (Num (a 
-> a)) 
prevents the assignment of a monomorphic type (its form violates the demands of 
the 
defaulting rules, http://haskell.org/onlinereport/decls.html#sect4.3.4), so it 
doesn't 
work.
Again, it would work with a type signature or with the monomorphism restriction 
turned 
off. 
The same (with minor modifications) applys to the "square . add3" variants.

> -- composition2 5 9 == 196
>
> composition3 x y = square . (add3 x y)-- composition3 1 2 3 == 36
> composition4 x y = square . add3 x y  -- composition4 1 2 3 == 36

composition4 is exactly the same as composition3, function application has 
higher 
precedence than composition, so both are parsed as

square . ((add3 x) y)

> composition5 x y = (square . add3) x y-- TODO: what does this mean?? 
> how
> do w

Re: [Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-01 Thread Mark Lentczner

On Dec 1, 2009, at 2:29 AM, Heinrich Apfelmus wrote:

>   data Train a b = Wagon a (Train a b)
>  | Loco  b

Surely that should be:

  data Train a b = Wagon a (Train a b)
 | Caboose b

?

- MtnViewMark

Mark Lentczner
http://www.ozonehouse.com/mark/
m...@glyphic.com



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


Re: [Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-01 Thread Nicolas Pouillard
Excerpts from Heinrich Apfelmus's message of Tue Dec 01 11:29:24 +0100 2009:
> Duncan Coutts wrote:
> > On Mon, 2009-11-30 at 06:08 +, Malcolm Wallace wrote:
> >> However, if you really want to terminate the stream at  
> >> the first error, and to reflect this in the type, then I guess you can  
> >> define your own list type:
> >>
> >> data ListThenError e a = Cons a (ListThenError e a)
> >> | Error e
> >>
> >> Of course this has the disadvantage that then your consumer must  
> >> change to use this type too.
> > 
> > I've been using this list type quite a lot recently. It's in the 'tar'
> > package for example. It comes with variants of the standard functions
> > foldl, foldr, unfoldr that take into account the error possibility.
> > 
> > At some point we should probably make a package to standardise and
> > document this lazy error handling idiom.
> 
> I propose to (trivially) generalize this type to "list with an end"
> 
>data ListEnd a b = Cons a (ListEnd a b)
> | End b
> 
> because it may have other uses than just lazy error handling. For
> mnemonic value, we could call it a "train":
> 
>data Train a b = Wagon a (Train a b)
>   | Loco  b
> 
> as it is in analogy with a sequence of wagons of the same type followed
> by the locomotive which has a different type.
> 
> 
> This data type naturally turns up as the differential of the lists
> 
>d [x] = Train x [x]
> 
> and the usual zipper ([x],[x]) is actually an optimization:
> 
>Train a b == ([a] , b)
> 
> Incidentally, this isomorphism corresponds to the alternative approach
> you mentioned:
> 
> > Another approach that some people have advocated as a general purpose
> > solution is to use:
> > 
> > data Exceptional e a = Exceptional {
> >   exception :: Maybe e
> >   result:: a
> > }
> 
> 
> As for other uses of  Train , I remember seeing the following fold operation
> 
>   fold1 :: (a -> b -> b) -> (a -> b) -> [a] -> b
>   fold1 f g [a]   = g a
>   foldl f g (a:x) = f a (fold1 f g x)

This proposition looks quite nice and gently subsume the ListThenError
type.

type ListThenError e a = Train a (Maybe e)

Anyone to put this on Hackage?

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


Re: [Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-12-01 Thread Duncan Coutts
On Mon, 2009-11-30 at 20:10 -0800, John Millikin wrote:
> On Mon, Nov 30, 2009 at 03:02, Duncan Coutts
>  wrote:

> >> data ListThenError e a = Cons a (ListThenError e a)
> >> | Error e
> >>
> >> Of course this has the disadvantage that then your consumer must
> >> change to use this type too.
> >
> > I've been using this list type quite a lot recently. It's in the 'tar'
> > package for example. It comes with variants of the standard functions
> > foldl, foldr, unfoldr that take into account the error possibility.
> >
> > At some point we should probably make a package to standardise and
> > document this lazy error handling idiom.
> 
> Wow, this is perfect! I've extracted that type out into the
> "failable-list" library[1], with a few added instances for common
> classes (Monad, Applicative, Traversable, etc).
> 
> [1] http://hackage.haskell.org/package/failable-list

Nice. The one I've felt is missing in the tar package was a foldl. This
is used to fully consume a failable list. It wants to return either the
normal foldl result or an error encountered.

When consuming with a foldr, the main use case is that you're
translating into another lazy data structure which has it's own place to
annotate errors.

When consuming with a foldl, the main use case is that you're strictly
consuming the list and purging out the errors because you want to
construct a type that does not have room in it for errors.

There seem to be a number of possibilities though:

for reference, standard list foldl:
foldl :: (b -> a -> b) -> b -> [a] -> b


foldl :: (b -> a -> b) -> b ->
  -> FailableList e a -> Either e b

or the final result as Either (e, b) b

foldl :: (b -> a -> b) -> b -> (b -> e -> b)
  -> FailableList e a -> b

foldl :: (b -> a -> b) -> b -> (b -> c) -> (b -> e -> c)
  -> FailableList e a -> b

This last one is basically the church encoding of Either (e, b) b.

Do we want the partial result at the point the list ended in error? If
not then it's a little simpler.

Duncan

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


[Haskell-cafe] Re: Help mixing pure and IO code

2009-12-01 Thread Heinrich Apfelmus
Luke Palmer wrote:
> Hector Guilarte  wrote:
>>
>> f:: [int] -> (a,[Int])
>> f randomList =
>> let (usedRandomNumber,newRandomList) = g randomList
>> in (usedRandomNumber,newRandomList)
> 
> This pattern can be encapsulated in a monad:
> 
> newtype RandM a = RandM { unRandM :: [Int] -> (a,[Int]) }
> 
> instance Monad RandM where
> [...]
> 
> See the similarity?
> 
> Of course, there is no need to implement this yourself.  It is already
> implemented as State [Int].  And as long as you are doing that, you
> might as well use Rand from the MonadRandom package.  In fact, I have
> argued that you should use MonadRandom instead of the lower-level
> System.Random whenever possible:
> http://lukepalmer.wordpress.com/2009/01/17/use-monadrandom/

The rationale being that  RandM a  has a natural interpretation as
"random variable of type a" with no reference to how it's actually
implemented.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-01 Thread Heinrich Apfelmus
Duncan Coutts wrote:
> On Mon, 2009-11-30 at 06:08 +, Malcolm Wallace wrote:
>> However, if you really want to terminate the stream at  
>> the first error, and to reflect this in the type, then I guess you can  
>> define your own list type:
>>
>> data ListThenError e a = Cons a (ListThenError e a)
>> | Error e
>>
>> Of course this has the disadvantage that then your consumer must  
>> change to use this type too.
> 
> I've been using this list type quite a lot recently. It's in the 'tar'
> package for example. It comes with variants of the standard functions
> foldl, foldr, unfoldr that take into account the error possibility.
> 
> At some point we should probably make a package to standardise and
> document this lazy error handling idiom.

I propose to (trivially) generalize this type to "list with an end"

   data ListEnd a b = Cons a (ListEnd a b)
| End b

because it may have other uses than just lazy error handling. For
mnemonic value, we could call it a "train":

   data Train a b = Wagon a (Train a b)
  | Loco  b

as it is in analogy with a sequence of wagons of the same type followed
by the locomotive which has a different type.


This data type naturally turns up as the differential of the lists

   d [x] = Train x [x]

and the usual zipper ([x],[x]) is actually an optimization:

   Train a b == ([a] , b)

Incidentally, this isomorphism corresponds to the alternative approach
you mentioned:

> Another approach that some people have advocated as a general purpose
> solution is to use:
> 
> data Exceptional e a = Exceptional {
>   exception :: Maybe e
>   result:: a
> }


As for other uses of  Train , I remember seeing the following fold operation

  fold1 :: (a -> b -> b) -> (a -> b) -> [a] -> b
  fold1 f g [a]   = g a
  foldl f g (a:x) = f a (fold1 f g x)

(from

  Oege de Moor, Jeremy Gibbons.
  "Bridging the Algorithm Gap: A Linear-Time Functional Program
for Paragraph Formatting"
  http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.47.3229

)

which is of course the natural  fold  for the  Train  data type:

  fold :: (a -> c -> c) -> (b -> c) -> Train a b -> c
  fold f g (Loco  b)   = g b
  fold f g (Wagon a t) = f a (fold f g t)



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Function composition questions from a newbie

2009-12-01 Thread newbie2009


leledumbo wrote:
> 
> None of them are legal, at least in my WinHugs they're not. What tools are
> you using?
> 

1) I am using GHCi. I put the following into a file named composition.hs and
typed ":l composition.hs" in GHCi. I also did a ":browse Main"
2) Next, I installed WinHugs, and loaded the same hs file. It failed with an
error when processing the definition for composition2
3) is GHC the standard Haskell implementation or should i be using WinHugs?

---8<---

square x = x * x
add x y = x + y
add3 x y z = x + y + z
composition1 = add . square
-- composition1 5 6 == 31

-- composition2 = square . add -- wont work

composition2 x = (square . add) x   -- to make it work, make composition2 
take
an argument
-- composition2 5 9 == 196

composition3 x y = square . (add3 x y)  -- composition3 1 2 3 == 36
composition4 x y = square . add3 x y-- composition4 1 2 3 == 36
composition5 x y = (square . add3) x y  -- TODO: what does this mean?? how do
we invoke composition5
composition6 x = (square . add3) x  -- TODO: what does this mean?? 
how do
we invoke composition5
composition7 x = (square . add3) x 8
composition8 x = (square . add3) 1 2 x
composition9 x = (square . add3) x
composition10 x = (square . add3) 1 2 3

---8<---


-- 
View this message in context: 
http://old.nabble.com/Function-composition-questions-from-a-newbie-tp26570201p26588106.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Function composition questions from a newbie

2009-12-01 Thread leledumbo

> I dont understand why the above functions are legal, and what arguments
they need. Could you please
> give an example of how to invoke it?

Huh? None of them are legal, at least in my WinHugs they're not. What tools
are you using?

Some good reading I found:
http://learnyouahaskell.com/higher-order-functions
http://www.uni-bonn.de/~manfear/haskell-functions.php

-- 
View this message in context: 
http://old.nabble.com/Function-composition-questions-from-a-newbie-tp26570201p26588093.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Re: Timing and Atom

2009-12-01 Thread Neil Davies

On 1 Dec 2009, at 05:44, Tom Hawkins wrote:




I never considered running Atom generated functions in an asynchronous
loop until you posted your "Atomic Fibonacci Server" example
(http://leepike.wordpress.com/2009/05/05/an-atomic-fibonacci-server-exploring-the-atom-haskell-dsl/ 
).

I'm curious how such a system would behave if it referenced a
hardware clock to enable and disable rules.  I can see how this could
be problematic for hard real-time, safety critical stuff.  But there
is a wide field of applications where this approach would work just
fine -- not having to worry about meeting a hard loop time would
certainly simplify the design.  Could some form of static analysis be
applied to provide the timing guarantees?



Yes this is possible. I work with Stochastic Process Algebras that  
have these properties.
With them it is possible to get strong probabilistic guarantees and,  
when combined with carefully
chosen priority and preemption model, you can have both 'hard' (i.e  
response within a given time with

probability 1) and softer guarantees (yet with known time CDF).

The really nice property is that, given that your problem will permit  
it, you can even create systems that
can go into saturation (arrival rate exceeds processing rate) and  
define how they will gracefully degrade.


We use this for constructing and analysing large scale distributed  
systems and reasoning about,
and controlling, their emergent properties including under overload  
and when the communications is lossy.


Neil

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


Re: [Haskell-cafe] Function composition questions from a newbie

2009-12-01 Thread newbie2009

I am a newbie. Consider this code: 

square x = x * x 
add3 x y z = x + y + z 


leledumbo wrote:
> 
> 
> what about (square . add3) 1 2?
> 
> It doesn't work since add3, when curried (arguments of square "blended"
> with add3's) with 1 argument becomes:
> 
> add3 :: Num a => a -> a -> a
> 
> which is a function that accepts 2 arguments and it's not compatible with
> square's a.
> 

Thank you so much for your clarification. To understand better, I tried some
definitions 
1) composition = (square . add3) 5 -- illegal as you had explained
2) composition x = (square . add3) 1 2 3 -- legal, but why? what is the
significance of x
3) composition x = (square . add3) x -- legal, but why?
4) composition x y = (square . add3) x y -- legal, but why?
5) composition x = (square . add3) x 3 -- legal, but why?


I dont understand why the above functions are legal, and what arguments they
need. Could you please give an example of how to invoke it?






-- 
View this message in context: 
http://old.nabble.com/Function-composition-questions-from-a-newbie-tp26570201p26587250.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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