Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Ketil Malde
"Jared Updike" <[EMAIL PROTECTED]> writes:

> On 6/12/06, Neil Mitchell <[EMAIL PROTECTED]> wrote:

>> I tend to use the module TextUtil (or Util.Text) from Yhc for these
>> kind of string manipulations:

> Funny. I have a module called Useful.hs with some of these same sorts
> of functions. (coming from Python where I used .split(',') and
> .replace('\r', '') and such a lot):

Clifford Beshers writes:

> Here is a solution using the Posix regex module.

In addition, there are similar things in John Goerzen's MissingH, and
in FPS.  It'd be nice if the Data.List interface included these.
Seems there is a two-d matrix, one is the split criterion (matching
element, number of elements, boolean function on elements), the other
is the return type (split off one (-> ([a],[a])) or split up the whole
string (-> [[a]])).  Arbitrarily¹ naming the former 'split' and
the latter 'break', you could have something like:

split :: a -> [a] -> ([a],[a])
splitAt :: Int -> [a] -> ([a],[a])
splitWhen :: (a -> Bool) -> [a] -> ([a],[a])

break :: a -> [a] -> [[a]]
breakAt :: Int -> [a] -> [[a]]
breakWhen :: (a -> Bool) -> [a] -> [[a]]

-k

¹ Well, perhaps not quite, it seems more natural to me to 'split in
two' and 'break into pieces'.
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Clifford Beshers

Donn Cave wrote:

Quoth Clifford Beshers <[EMAIL PROTECTED]>:
| Well, I couldn't resist the puzzle.  Here are solutions using foldr and 
| unfoldr.  Don't know if they are cunning or not, but they were kind of fun.


...
| splitByElem1 e xs =
| foldr f [[]] xs
| where f a b = if a == e then [] : b else (a : head b) : (tail b)

This does the right thing with trailing separators, which is not to be
taken for granted among Haskell split implementations.  The splits I have
been seeing in this thread are conservative, so if the separator is ':',
then "::a" splits to ["", "", "a"].  Frequently however the implementation
fails to deal with the trailing separator, so "a:" is ["a"], where it
should be ["a", ""].  It's not something you run into right away.

In a liberal split, "a " should indeed be ["a"], but that's a different
matter.  Neither of the two I've looked at seems to be shooting for a
liberal "words" white space split.
Good point.  My solutions are inconsistent on white space, which I don't 
like.


Your criterion eliminates this solution as well:

filter (/= ",") $ groupBy (\x y -> x /= ',' && y /= ',') "Haskell, 
Haskell, and Haskell,"

["Haskell"," Haskell"," and Haskell"]

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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Donn Cave
Quoth Clifford Beshers <[EMAIL PROTECTED]>:
| Well, I couldn't resist the puzzle.  Here are solutions using foldr and 
| unfoldr.  Don't know if they are cunning or not, but they were kind of fun.

...
| splitByElem1 e xs =
| foldr f [[]] xs
| where f a b = if a == e then [] : b else (a : head b) : (tail b)

This does the right thing with trailing separators, which is not to be
taken for granted among Haskell split implementations.  The splits I have
been seeing in this thread are conservative, so if the separator is ':',
then "::a" splits to ["", "", "a"].  Frequently however the implementation
fails to deal with the trailing separator, so "a:" is ["a"], where it
should be ["a", ""].  It's not something you run into right away.

In a liberal split, "a " should indeed be ["a"], but that's a different
matter.  Neither of the two I've looked at seems to be shooting for a
liberal "words" white space split.

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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Clifford Beshers
Well, I couldn't resist the puzzle.  Here are solutions using foldr and 
unfoldr.  Don't know if they are cunning or not, but they were kind of fun.


import Data.List

splitByElem e xs =
   unfoldr f xs
   where f s =
 case break (e ==) s of
   ("",_) -> Nothing
   (a,b) -> Just (a, drop 1 b)


splitByElem1 e xs =
   foldr f [[]] xs
   where f a b = if a == e then [] : b else (a : head b) : (tail b)



J. Garrett Morris wrote:


There is at least one cunning rewriting with foldl, I think, but I
think this version is clearer.

/g

On 6/12/06, Sara Kenedy <[EMAIL PROTECTED]> wrote:

Hi all,

I want to write a function to separate a string into a list of strings
separated by commas.

Example:
separate :: String -> [String]

separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", 
"and Haskell"]


If anyone has some ideas, please share with me. Thanks.

S.
___
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] Separate a string into a list of strings

2006-06-12 Thread Clifford Beshers

Brandon Moore wrote:


Going by man grep, those [:foo:] classes are only special inside a 
character class, otherwise [:space:]* = [aceps:]*.


  Prelude Text.Regex> splitRegex (mkRegex "[[:space:]]*,[[:space:]]*")
  "Haskell, Haskell, and Haskell"
  ["Haskell","Haskell","and Haskell"]


The smart money was on user error.   Thanks.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Neil Mitchell

Hi


beginsWith []   [] = True
beginsWith _[] = True
beginsWith []   _  = False
beginsWith (a:aa)   (b:bb)
| a == b   = aa `beginsWith` bb
| otherwise= False


I used to have this in my library then I discovered isPrefixOf :) (or
flip isPrefixOf, I think in this case)


endsWith a b = beginsWith (reverse a) (reverse b)

ditto, isSuffixOf

Thanks

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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Jared Updike

Funny. I have a module called Useful.hs with some of these same sorts
of functions. (coming from Python where I used .split(',') and
.replace('\r', '') and such a lot):

--
module Useful where

import List ( intersperse, tails )
import Numeric ( readHex )

hex2num :: (Num a) => String -> a
hex2num s = let (result, _):_ = readHex s in result

toEnv s = map tuple (split ';' s)

tuple :: String -> (String, String)
tuple line = case split '=' line of
  a:b:_ -> (a,b)
  a:_   -> (a,"")
  _ -> ("","") -- not good, probably won't happen for my typical usage...

split   :: Char -> String -> [String]
split _ ""  =  []
split c s   =  let (l, s') = break (== c) s
in  l : case s' of
  []  -> []
  (_:s'') -> split c s''

beginsWith []   [] = True
beginsWith _[] = True
beginsWith []   _  = False
beginsWith (a:aa)   (b:bb)
   | a == b   = aa `beginsWith` bb
   | otherwise= False

dropping [] [] = []
dropping [] _  = []
dropping x  [] = x
dropping s@(a:aa) (b:bb) | a == b= dropping aa bb
| otherwise = s

-- replace all occurrences of 'this' with 'that' in the string 'str'
-- like Python replace
replace __[]  = []
replace this that str
   | str `beginsWith` this = let after = (str `dropping` this)
  in  that ++ replace this that after
   | otherwise =
   let x:xs = str
 in x : replace this that xs

eat s = replace s ""

-- sometimes newlines get out of hand on the end of form POST submissions,
-- so trim all the end newlines and add a single newline
fixEndingNewlines = reverse . ('\n':) . dropWhile (=='\n') . reverse .
filter (/= '\r')

endsWith a b = beginsWith (reverse a) (reverse b)

a `contains` b = any (`beginsWith` b) $ tails a
--

 Jared.

On 6/12/06, Neil Mitchell <[EMAIL PROTECTED]> wrote:

Hi,

I tend to use the module TextUtil (or Util.Text) from Yhc for these
kind of string manipulations:

http://www-users.cs.york.ac.uk/~malcolm/cgi-bin/darcsweb.cgi?r=yhc;a=headblob;f=/src/compiler98/Util/Text.hs

separate = splitList ","

I am currently thinking about making this module into a standalone
library with some other useful functions, if people have any opinions
on this then please let me know.

Thanks

Neil


On 6/12/06, Sara Kenedy <[EMAIL PROTECTED]> wrote:
> Hi all,
>
> I want to write a function to separate a string into a list of strings
> separated by commas.
>
> Example:
> separate :: String -> [String]
>
> separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and 
Haskell"]
>
> If anyone has some ideas, please share with me. Thanks.
>
> S.
> ___
> 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




--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Everything but the lazyness - idea for force/delay lists

2006-06-12 Thread Brian Hulley

Hi -

I've been thinking about how to get an extremely fast language with all the 
benefits of Haskell ie completely pure with no side effects, but with 
monads, higher order functions, type classes etc, but without the lazyness.


I know this is controversial, but having started to write a serious program 
in Haskell, I find that almost all of it doesn't need any lazyness at all, 
yet I have to constantly mess up my code by using Tuple2 a b instead of 
(a,b), ! in all my data types, and millions of brackets to use $! (which has 
the wrong associativity for passing multiple arguments strictly) etc and I 
can't do anything about the slowness and possible space leaks introduced by 
library functions which are lazy, not to mention the fact that afaiu the 
lifted type system necessary for any language which supports lazyness, and 
general undecidability results means that it will probably be impossible to 
ever compile lazy code to be as fast as OCaml etc.


(This is not to say Haskell is too slow - I find the app I'm writing at the 
moment runs fast enough (given all my strictness annotations) it's just that 
lazyness is making my life more difficult rather than easier and is probably 
also costing something in terms of speed.)


The one place where I'm using lazyness is where I need to glue the output of 
one computation to another by using a lazy list. In effect I'm using a lazy 
list as the equivalent of an iterator in C++ - the elements are only created 
when needed, but once read, I only read them once, so I don't need the 
memoization properties of lazyness.


When I first started to learn Haskell, I thought lazyness was essential for 
monads and hence an acceptable price to pay for using them. However I now 
think that monads would work perfectly without lazyness, since they are 
usually always defined in terms of >>= (not >> as I'd thought when I didn't 
know Haskell).


Other uses of lazyness are of course infinite structures and fixpoints etc.

I think the use of a lazy list as a read-once-on-demand stream could be 
achieved just as easily by a strict language with some syntactic sugar by 
redefining the meaning of []:


   data GlueList a = Empty | Cons a [a]

   type [a] = () -> GlueList a

   force :: (() -> a) -> a
   force f = f ()

Pattern matching could then be changed so that

   p [a] = exp

is short for:

p x = case force x of
Cons a y -> case force y of
Empty -> exp

and

   p [h|t] = exp-- Prolog style list sugar

   p x = case force x of
  Cons h t -> exp

and in an expression, [exp1,...] would be expanded into the appropriate 
delayed construction eg:


   x = [a]

   x = \() -> Cons a (\() -> Empty)

(List comprehensions could just be written using do notation).

There could also be extra syntactic support for force/delay eg !exp to mean 
exp () and ~exp to mean \()->exp. With this extra sugar, it might be 
relatively painless to still use infinite data structures.


Lazyness seems to sometimes be used to accomplish things that could easily 
be implemented in other ways, perhaps even better, and with more control 
(and certainly more explicitness) over the exact aspect of lazyness that is 
being used in a certain situation eg memoization, desugared attribute 
grammars, list-as-glue, etc.


The advantages would be that the resulting language would be simpler to 
understand and could execute like lightning so there would be no need to use 
C or ML ever again.


Afaik the full speed advantage can't be achieved just by syntactic sugar for 
regular Haskell since regular Haskell, even with seq etc, still needs to use 
a lifted type system, but syntactic sugar could certainly be used to 
implement such a language on top of Haskell to investigate if the complete 
absence of lazyness would cause any problems in practice. If I get time I 
might try to do this but I've shared the idea here in the vague hope someone 
else might want to do it first :-)


There certainly seems to be a "gap in the market" between the perfection of 
lazy Haskell's monads, typeclasses etc and strict ML's side effects and less 
expressive type system.


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Brandon Moore

Clifford Beshers wrote:

Sara Kenedy wrote:


Hi all,

I want to write a function to separate a string into a list of strings
separated by commas.

Example:
separate :: String -> [String]

separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and 
Haskell"]


If anyone has some ideas, please share with me. Thanks.


Here is a solution using the Posix regex module.

Prelude Text.Regex> splitRegex (mkRegex "[ \t]*,[ \t]*") "Haskell,
Haskell, and Haskell"
["Haskell","Haskell","and Haskell"]

This form should work regardless of locale, but appears to be broken, 
although I expect this is either my fault or that of the underlying 
Posix library:


Prelude Text.Regex> splitRegex (mkRegex "[:space:]*,[:space:]*")
"Haskell, Haskell, and Haskell"
["Haskell"," Haskell"," and Haskell"]


Going by man grep, those [:foo:] classes are only special inside a 
character class, otherwise [:space:]* = [aceps:]*.


  Prelude Text.Regex> splitRegex (mkRegex "[[:space:]]*,[[:space:]]*")
  "Haskell, Haskell, and Haskell"
  ["Haskell","Haskell","and Haskell"]

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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Clifford Beshers




Sara Kenedy wrote:
Hi all,
  
  
I want to write a function to separate a string into a list of strings
  
separated by commas.
  
  
Example:
  
separate :: String -> [String]
  
  
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and
Haskell"]
  
  
If anyone has some ideas, please share with me. Thanks.
  

Here is a solution using the Posix regex module.
Prelude Text.Regex> splitRegex (mkRegex "[ \t]*,[ \t]*")
"Haskell, Haskell, and Haskell"
["Haskell","Haskell","and Haskell"]

This form should work regardless of locale, but appears to be broken,
although I expect this is either my fault or that of the underlying
Posix library:
Prelude Text.Regex> splitRegex (mkRegex
"[:space:]*,[:space:]*") "Haskell, Haskell, and Haskell"
["Haskell"," Haskell"," and Haskell"]




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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Neil Mitchell

Hi,

I tend to use the module TextUtil (or Util.Text) from Yhc for these
kind of string manipulations:

http://www-users.cs.york.ac.uk/~malcolm/cgi-bin/darcsweb.cgi?r=yhc;a=headblob;f=/src/compiler98/Util/Text.hs

separate = splitList ","

I am currently thinking about making this module into a standalone
library with some other useful functions, if people have any opinions
on this then please let me know.

Thanks

Neil


On 6/12/06, Sara Kenedy <[EMAIL PROTECTED]> wrote:

Hi all,

I want to write a function to separate a string into a list of strings
separated by commas.

Example:
separate :: String -> [String]

separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]

If anyone has some ideas, please share with me. Thanks.

S.
___
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] Learning C after Haskell

2006-06-12 Thread Duncan Coutts
On Mon, 2006-06-12 at 14:48 -0700, Jared Updike wrote:
> > Thanks, Minh. So are things like recursion and memory sharing typically out
> > the window?
> 
> Recursion works in C, but every function call pushes stack, so
> recursive depth is limited by RAM (compare to tail call optimization
> in many functional programming languages where the stack frame is
> reused if code is written iteratively with an accumulator). Most of
> the time for performance (and to be idiomatic) in C you will just
> write for and while loops and modify state in place. Welcom to C.

GCC can do a limited tail-call optimisation these days. It covers the
obvious self tail call case and I believe some less trivial cases but
it's not as comprehensive as in a typical functional language compiler.

Duncan

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


Re: [Haskell-cafe] Learning C after Haskell

2006-06-12 Thread Jared Updike

Thanks, Minh. So are things like recursion and memory sharing typically out
the window?


Recursion works in C, but every function call pushes stack, so
recursive depth is limited by RAM (compare to tail call optimization
in many functional programming languages where the stack frame is
reused if code is written iteratively with an accumulator). Most of
the time for performance (and to be idiomatic) in C you will just
write for and while loops and modify state in place. Welcom to C.

 Jared.
--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Learning C after Haskell

2006-06-12 Thread Chad Scherrer
Thanks, Minh. So are things like recursion and memory sharing typically out the window?



Also, I don't see how thinking about type classes will help, without the benefits of polymorphism.


-Chad-- Forwarded message --From: minh thu <[EMAIL PROTECTED]>Date: Jun 12, 2006 12:23 PM
Subject: Re: [Haskell-cafe] Learning C after HaskellTo: Chad Scherrer <[EMAIL PROTECTED]>hi,C is very different from Haskell.* you'lle have to manage explicitly memory de/allocation.
* c programming is a bit like haskell io monad programming (butwithout the functionnal part) :  you'lle use "=" in place of "<-" and the left hand side can bereassigned multiple times.
* imperative programming (c is imperative) involve states (a lot !).  (see how to write the equivalent of mapM print [1..10]);  imperative programmers use loops, not much recursion* things you can keep in your mind : the way you organize things
(module, type classes (but there is no polymorphism in c), havefunctions and not a huge amount of code lines...), the way you useself documenting names.well, not sure it helps, but here you are :)mt
2006/6/12, Chad Scherrer <[EMAIL PROTECTED]>:> Ok, so I'm doing things somewhat backward. I've been using Haskell for a> while now, whenever I get a chance to. But in order to become more involved
> in high-performance computing projects at my work, I need to learn C.>> I've heard a lot of people say that experience in Haskell can improve one's> abilities in other languages, but I also wonder how different the C "way of
> doing things" is different from Haskell's.>> My question is, as I learn C, are there any particular Haskell concepts I> should keep in the back of my mind, or is it better to approach C from
> scratch?>> Thanks in advance!>> Preparing for a foot-shooting,> Chad>> ___> Haskell-Cafe mailing list> 
Haskell-Cafe@haskell.org> http://www.haskell.org/mailman/listinfo/haskell-cafe>>>-- Chad Scherrer
"Time flies like an arrow; fruit flies like a banana" -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread J. Garrett Morris

Off the top of my head:

separate :: String -> [String]
separate [] = []
separate s =
 case break (',' ==) s of
   (s,[]) -> [s]
   (s,',':s') -> s : separate s'
   _ -> error "how did we get here?"

There is at least one cunning rewriting with foldl, I think, but I
think this version is clearer.

/g

On 6/12/06, Sara Kenedy <[EMAIL PROTECTED]> wrote:

Hi all,

I want to write a function to separate a string into a list of strings
separated by commas.

Example:
separate :: String -> [String]

separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]

If anyone has some ideas, please share with me. Thanks.

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




--
We have lingered in the chambers of the sea 
By sea-girls wreathed with seaweed red and brown
Till human voices wake us, and we drown.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] newbie type signature question

2006-06-12 Thread Brian Hulley

Bulat Ziganshin wrote:

Hello Brian,

Saturday, June 10, 2006, 3:05:25 AM, you wrote:


It is possible that this feature was added to the language for the
benefit of people who prefer not to use explicit type signatures but
afaiu this goes against best practice where everything should always
have an explicit signature to make code easy to understand and
facilitate debugging of type errors.


when you work with C++ or some other OOP language, you can define that
some field in structure should some some specific interface and this
allows to use functions of this interface on this field. i required
the same feature in Haskell, for example:

data UTF8Stream h = (ByteStream h) => UTF8Stream h

instance TextStream (UTF8Stream h) ...

addUTF8Encoding :: h -> (UTF8Stream h)

and so on. currently i should add type constraint to each and every
class and function i declared.


Hello Bulat -
Thanks for the example. Afaiu, if you don't write any type signature at all, 
type inference will infer the constraint, at least this is what I understand 
from http://haskell.org/onlinereport/decls.html section 4.2.1:


   data Eq a => Set a = NilSet | ConsSet a (Set a)
   Pattern matching against ConsSet also gives
   rise to an Eq a constraint. For example:

 f (ConsSet a s) = a

   the function f has inferred type Eq a => Set a -> a.

At the moment when you have an explicit type signature you can see exactly 
what the function needs, so that if you later refactored the code you could 
see which functions actually used the Eq a constraint and which ones didn't. 
For example a function to find the size of a set probably wouldn't need Eq 
a.


So if the compiler was allowed to add a context to an explicit type 
signature you would no longer be able to just look at the type signature for 
a function to find out what it was making use of - you'd need to also look 
at all the data declarations and gather all the constraints together, to 
arrive at the full type signature.


Nevertheless I suppose it would be useful to have some kind of compiler flag 
to allow this - certainly given that contexts are allowed on data 
declarations it is kind of awkward having to "repeat" all the info on each 
function that uses that type, since at the moment the only way to avoid this 
repetition is to avoid giving functions that use that type any type 
signatures at all, which seems worse.


Or perhaps there could be a special syntax to indicate a partial type 
signature, that the compiler would complete by adding the contexts eg:


 f ::: Set a -> a
   ^^^ ? 3 colons to indicate that the compiler will add the relevant 
context(s)



i don't tried using existential types
here, so i'm not sure that they will give the same high speed for
inlined functions. moreover, they "lose" information about other type
classes that 'h' supports, although functions from these classes may
be required for application that use "UTF8Stream h" and even by other
definitions in my lib:

instance (ByteStringStream h) => ByteStringStream (UTF8Stream h) ...


Yes I also think they'd be slower and not recommended unless they're 
actually needed eg for getting a common interface to objects whose concrete 
types aren't known at compile time (being like virtual functions in C++). I 
just mentioned them as an example of something not relevant to the 
guideline. (Whoever wrote the guideline might have had more reasons but 
that's all I can think up so far.)


Best regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


[Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Sara Kenedy

Hi all,

I want to write a function to separate a string into a list of strings
separated by commas.

Example:
separate :: String -> [String]

separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]

If anyone has some ideas, please share with me. Thanks.

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


Re: [Haskell-cafe] Learning C after Haskell

2006-06-12 Thread Jason Dagit

On 6/12/06, Chad Scherrer <[EMAIL PROTECTED]> wrote:

Ok, so I'm doing things somewhat backward. I've been using Haskell for a
while now, whenever I get a chance to. But in order to become more involved
in high-performance computing projects at my work, I need to learn C.

[snip]

 My question is, as I learn C, are there any particular Haskell concepts I
should keep in the back of my mind, or is it better to approach C from
scratch?


Sounds like you would be an almost ideal user for Jekyll.  Too bad
it's only in the alpha stages:

http://jekyllc.sourceforge.net/

You might find it useful to study how Haskell's familiar product and
sum types would be represented in unfamiliar C.  If I recall correctly
you can find examples of the translation in the Jekyll
presentations/documentation.  So even if you never used it, it would
be a worthwhile read.

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


Re: [Haskell-cafe] Learning C after Haskell

2006-06-12 Thread Greg Buchholz
Chad Scherrer wrote:
> My question is, as I learn C, are there any particular Haskell concepts I
> should keep in the back of my mind, or is it better to approach C from
> scratch?

One thing from Haskell I'd try keep in mind is to minimize side
effects and keep the scope of side effects as contained and local as
possible.  So avoid mutating global variables, try not to write to the
same file from multiple different subroutines, etc. 

   And if you start getting seg-faults, you'll probably want a tool to
help you, since reasoning and debug by printf on pointers can only take
you so far in a language like C.

http://www.gnu.org/software/libc/manual/html_node/Allocation-Debugging.html
http://perens.com/FreeSoftware/ElectricFence/ 
http://valgrind.org/


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


[Haskell-cafe] Learning C after Haskell

2006-06-12 Thread Chad Scherrer
Ok, so I'm doing things somewhat backward. I've been using Haskell for
a while now, whenever I get a chance to. But in order to become more
involved in high-performance computing projects at my work, I need to
learn C. 

I've heard a lot of people say that experience in Haskell can improve
one's abilities in other languages, but I also wonder how different the
C "way of doing things" is different from Haskell's. 
My question is, as I learn C, are there any particular Haskell concepts
I should keep in the back of my mind, or is it better to approach C
from scratch?

Thanks in advance!
Preparing for a foot-shooting,Chad
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie: safe program termination in Windows

2006-06-12 Thread Alberto G. Corona
Hi,
I have a program that handle cached data. I don´t find the way to store
the data when the program is killed by other program. There is nothing
similar to signal in the Windows implementation and no exception
appears to trigger when the program is killed by a service handler or
by the Task manager

Anyone knows how to deal with that?.



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


Re: [Haskell-cafe] HCAR

2006-06-12 Thread Donald Bruce Stewart
stefan:
> Tashdid,
> 
> >does anyone know what happened to HCAR?
> >or HWN?
> 
> I guess the May ;) 2006 edition of HCAR will appear soon. I'm not  
> sure about what happened to HWN the last couple of weeks, though, but  
> I think that Donald is just quite busy these days.

Yep, that's the case. Expect an issue tomorrow though.

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


Re: [Haskell-cafe] Re: Cabal and linking with static libs (.a files)

2006-06-12 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes:

>> But it's quite easy: just copy the .a files from /usr/lib (or
>> wherever) and put them in the same place as your libHSpackage.a.

> I managed to get it to work by following that advice, and also
> renaming foo.a to libfoo.a, and linking with -lfoo.

Now you see it, now you don't. :-/

* .a files in /local/lib/foo-0.0/ghc-/  -- check
* .a files named libfoo.a   -- check
* -lfoo on the command line -- check

Using strace shows that the .a file is indeed being read by ghc, but I
still get "undefined reference".

Apologies for being dense, but I can't seem to make it work at all.
Is there a cabalized library that does this (links to a .a type C
library) that I can look at?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] HCAR

2006-06-12 Thread Stefan Holdermans

Tashdid,


does anyone know what happened to HCAR?
or HWN?


I guess the May ;) 2006 edition of HCAR will appear soon. I'm not  
sure about what happened to HWN the last couple of weeks, though, but  
I think that Donald is just quite busy these days.


Regards,

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


[Haskell-cafe] HCAR

2006-06-12 Thread Imam Tashdid ul Alam
does anyone know what happened to HCAR? 
or HWN?

__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] newbie type signature question

2006-06-12 Thread Simon Peyton-Jones
you need at least one constructor if you say 'where'.  

S

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Brock
| Peabody
| Sent: 09 June 2006 20:34
| To: haskell-cafe@haskell.org
| Subject: RE: [Haskell-cafe] newbie type signature question
| 
| > From: Brandon Moore
| 
| > Getting them both is tricky, but you can do it if you use a GADT to
| > write a type that means "exists a such that a = m and a is a Monad":
| 
| Is GADT a way to assemble types at compile-time?  It looks really
cool.
| 
| > {-# OPTIONS -fglasgow-exts #-}
| > data TyEq (a :: * -> *) (b :: * -> *) where
|   ^
|   ^
| 
| Compiling this fails here (the first '*') for me with "parse error on
| input '*'" (ghc 6.4.1), but I'll keep playing with it.
| 
| Thanks,
| 
| Brock
| 
| 
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Cabal and linking with static libs (.a files)

2006-06-12 Thread Ketil Malde
Simon Marlow <[EMAIL PROTECTED]> writes:

> What you actually want to do, I suspect, is to include verbatim copies
> of the .a dependencies in your (binary) Cabal package, to make it
> self-contained.

Exactly.

> But it's quite easy: just copy the .a files from /usr/lib (or
> wherever) and put them in the same place as your libHSpackage.a.

Thanks!

I managed to get it to work by following that advice, and also
renaming foo.a to libfoo.a, and linking with -lfoo.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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