Re: [Haskell-cafe] Haskell, C and Matrix Multiplication

Rather than commenting on the code provided, here are the two biggest wins
I've had recently with Haskell. Both of these are part of a physical
modeling project.
1) uu-parsinglib - simple to use and automatic error correction. I really,
really enjoy working with this library, and how often can you say that?
2) STM - the original design reads a system and all inputs from a config
file, then runs the system and produces output. I wanted to build the
system from a file but collect inputs and produce output in real-time.
After a few small adjustments, a few TVar's and a TMVar, and three
forkIO's, it was working.
One concern is that the engine (which is computation-intensive) shouldn't
block waiting for input, it should just continue on and catch up later.
With STM, this can be expressed as:
atomically $ getInputs inputTVar `orElse` return ()
and there's the desired behavior. Couldn't be easier.
John
From: Blake Rain
Dear Haskellers,
I thought I'd take some time to share something of my weekend with you all. Not because of anything new, but because it is a feel-good example of Haskell being win. A good read for Monday morning, perhaps.
<code snipped>
Now over to you guys! What experiences have you had which make you glad you use Haskell? Anything make you smile recently?
- Blake

-- My intension is that the PERSON class should *specify* -- that a person has a constant id called p1 -- and that a person has a name that can be found from the id. class PERSON a b where p1 :: a name :: a -> b -- My intension is that the instance should implement the PERSON class instance PERSON Int String where p1 = 1 name p1 = "john" -- -- Why does the evaluations of p1 or name p1 produce errors? -- how do I fix them and still keep the basic instance-implements-class relation? -- Thanks, -- Pat This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

On Mon, 17 Jan 2011, Patrick Browne wrote:
-- My intension is that the PERSON class should *specify* -- that a person has a constant id called p1 -- and that a person has a name that can be found from the id. class PERSON a b where p1 :: a name :: a -> b
-- My intension is that the instance should implement the PERSON class instance PERSON Int String where p1 = 1 name p1 = "john"
-- Why does the evaluations of p1 or name p1 produce errors? -- how do I fix them and still keep the basic instance-implements-class relation?
The problem is certainly, that a Haskell interpreter has no way to infer types, thus you have to annotate type of both argument and result of 'name', and type annotation for 'p1' is not possible at all, because 'b' does not occur in its type. You have to write name (12::Int) :: String But I suspect, what you try to do is not what you need. If you tell us what you want to do, we can certainly give more helpful answers. Maybe you want to do something with functional dependencies, such that 'String' result type is automatically chosen if the argument type is 'Int'. But before suggesting this type extension, I'd like to know more about your problem.

Henning, The code is not intended to fit into a larger application. I am trying to understand instance-implements-class relation. My experiment consists of writing simple English sentences and then seeing how they could be specified and implemented in Haskell. I am sure that this simple requirement could easily be coded in Haskell, but I studying how to specify the requirement using type classes. The bottom line is I want to stay with plain vanilla type classes. If there is no simple way to do this using type classes then I am obviously using the wrong technique. Thanks, Pat On 17/01/2011 11:39, Henning Thielemann wrote:
But I suspect, what you try to do is not what you need. If you tell us what you want to do, we can certainly give more helpful answers.
Maybe you want to do something with functional dependencies, such that 'String' result type is automatically chosen if the argument type is 'Int'. But before suggesting this type extension, I'd like to know more about your problem.
I am trying to understand instance-implements-class relation. This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

Henning Thielemann
class PERSON a b where p1 :: a name :: a -> b
A multi-parameter typeclass is a relation over types...
instance PERSON Int String where p1 = 1 name p1 = "john" ^--note that this is just an unused paramter, it is clearer to specify 'name _ = "john"'
...so this instance gives the PERSON relation for Int and String. So other PERSONs would have different types, say: instance PERSON Double Int where p1 = 3.14 name = 200 Does that make sense? It looks a bit strange to me.
The problem is certainly, that a Haskell interpreter has no way to infer types, thus you have to annotate type of both argument and result of 'name', and type annotation for 'p1' is not possible at all, because 'b' does not occur in its type. You have to write
name (12::Int) :: String
And (correct me if I'm wrong) there's no way to do that for p1, since there is no way to specify which type 'b' you want. You could have instance PERSON Int String where p1 = 1 name = "john" and instance PERSON Int Double where p1 = 24 name = 3.14 then the system would have no way to figure out which value you want even if you specify (p1::Int). Are you sure you didn't want: data Person = P Int String ? -k -- If I haven't seen further, it is by standing in the footprints of giants

On 17/01/2011 13:04, Ketil Malde wrote:
So other PERSONs would have different types, say:
I think the problem is there is just one constant p1 in the class and there needs to be multiple constants in the implementation (one for each person). It seems difficult to specify this using type classes So, some data declaration as you suggest will probably be needed. Thanks, Pat This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

Patrick Browne
I think the problem is there is just one constant p1 in the class and there needs to be multiple constants in the implementation (one for each person). It seems difficult to specify this using type classes So, some data declaration as you suggest will probably be needed.
Yes. I'm going to assume you're a beginner here (always a dangerous assumption on this list, no offense if I just misinterpret what you're trying to do). The (one?) difference between a Haskell class and a typical OO class, is that an instance of a class in Haskell is a *type*, but an instance of a class in, say, C++, is an object (which we like to call a *value*, to dissociate ourselves from That Other Crowd :-). Let's ignore the 'name' for now. class Person p where id :: p means that a *type* p is in the Person class if you can identify a value of type p that is the person-id for that type. So Int is a person-type if you say instance Person Int where id = 42 and (id::Int) will return 42 in subsequent code. Similarly, you can make other Person-types by instantiating them and defining id¹ for them. A function can take a Person-type as a parameter, for instance foo :: Person p => p -> Bool foo x = bla blah (id x) blah Alternatively, data Person = P Int on the other hand declares a new type called "Person", with a data constructor (tag) P, and containing just an Int. This means you can make multiple values of this type, so P 4, P 42, and P 911 are all Persons your program can juggle around in your program. A function can take these persons: foo :: Person -> Int -> Bool foo (P x) y = bla bla apply int functions on x and y Hope that was helpful? -k ¹ Dumb name, as this is the identity function. Sorry. -- If I haven't seen further, it is by standing in the footprints of giants

A functional dependency seems to allow me to express my rather strange requirement. class Person i n | i -> n where pid :: i name :: i -> n instance Person Int String where pid = 1 name(1) = "john" -- name(pid::Int) will produce john Thanks for your help Pat On 17/01/2011 14:07, Patrick Browne wrote:
On 17/01/2011 13:04, Ketil Malde wrote:
So other PERSONs would have different types, say:
I think the problem is there is just one constant p1 in the class and there needs to be multiple constants in the implementation (one for each person). It seems difficult to specify this using type classes So, some data declaration as you suggest will probably be needed.
Thanks, Pat
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

I don't think that's exactly what you want, though. name (2::Int)
crashes your program.
I think you really want a data type.
data Person a b = P a b
pid :: Person a b -> a
pid (P a _) = a
pname :: Person a b -> b
pname (P _ b) = b
Now, what it looks like you want is some kind of extensible relation
name 1 = "john"
name 2 = "julie"
etc.
but there's no simple way to specify this as an open function at the
value level. You can make a list of all the people:
people = [ P 1 "john", P 2 "julie" ]
name :: Int -> Maybe String
name x = fmap pname $ safeHead $ filter ((== x) . pid) people
safeHead [] = Nothing
safeHead (x:_) = Just x
It's still not really clear what you are trying to do.
-- ryan
On Mon, Jan 17, 2011 at 9:15 AM, Patrick Browne
A functional dependency seems to allow me to express my rather strange requirement.
class Person i n | i -> n where pid :: i name :: i -> n
instance Person Int String where pid = 1 name(1) = "john"
-- name(pid::Int) will produce john
Thanks for your help
Pat
On 17/01/2011 14:07, Patrick Browne wrote:
On 17/01/2011 13:04, Ketil Malde wrote:
So other PERSONs would have different types, say:
I think the problem is there is just one constant p1 in the class and there needs to be multiple constants in the implementation (one for each person). It seems difficult to specify this using type classes So, some data declaration as you suggest will probably be needed.
Thanks, Pat
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 19/01/2011 10:41, Ryan Ingram wrote:
It's still not really clear what you are trying to do.
I am trying to see what how this requirement can be represented using just the normal instance-implements-class relation for a comparison with a specification language approach. If there is no simple way to do this using type classes then I am obviously mis-using the technique. Regards, Pat This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

On Wed, Jan 19, 2011 at 11:56 PM, Patrick Browne
I am trying to see what how this requirement can be represented using just the normal instance-implements-class relation for a comparison with a specification language approach.
If there is no simple way to do this using type classes then I am obviously mis-using the technique.
Going back to your original message: -- My intension is that the PERSON class should *specify* -- that a person has a constant id called p1 -- and that a person has a name that can be found from the id. You can do this with type level numerals. data Z data S a type Zero = Z type One = S Zero type Two = S One -- etc class PersonId a where name :: a -> String instance PersonId Z where name _ = "John" instance PersonId (S Z) where name _ = "Julie" main = putStrLn (name (undefined :: One)) -- prints "Julie" -- ryan

Ryan, This is exactly what I was looking for. Thanks, Pat On 20/01/2011 18:56, Ryan Ingram wrote:
On Wed, Jan 19, 2011 at 11:56 PM, Patrick Browne
wrote: I am trying to see what how this requirement can be represented using just the normal instance-implements-class relation for a comparison with a specification language approach.
If there is no simple way to do this using type classes then I am obviously mis-using the technique.
Going back to your original message:
-- My intension is that the PERSON class should *specify* -- that a person has a constant id called p1 -- and that a person has a name that can be found from the id.
You can do this with type level numerals.
data Z data S a
type Zero = Z type One = S Zero type Two = S One -- etc
class PersonId a where name :: a -> String
instance PersonId Z where name _ = "John" instance PersonId (S Z) where name _ = "Julie"
main = putStrLn (name (undefined :: One)) -- prints "Julie"
-- ryan
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

On 20/01/2011 18:56, Ryan Ingram wrote:
On Wed, Jan 19, 2011 at 11:56 PM, Patrick Browne
wrote: I am trying to see what how this requirement can be represented using just the normal instance-implements-class relation for a comparison with a specification language approach.
If there is no simple way to do this using type classes then I am obviously mis-using the technique. Going back to your original message:
-- My intension is that the PERSON class should *specify* -- that a person has a constant id called p1 -- and that a person has a name that can be found from the id.
You can do this with type level numerals.
data Z data S a
type Zero = Z type One = S Zero type Two = S One -- etc
class PersonId a where name :: a -> String
instance PersonId Z where name _ = "John" instance PersonId (S Z) where name _ = "Julie"
main = putStrLn (name (undefined :: One)) -- prints "Julie"
Do the ids need to be numbers? You could also define data John data Julie instance PersonId John where name _ = "John" instance PersonId Julie where name _ = "Julie"
participants (5)
-
Henning Thielemann
-
John Lato
-
Ketil Malde
-
Patrick Browne
-
Ryan Ingram