Re: [Haskell-cafe] Proposal: new function for lifting

2013-09-28 Thread Marc Ziegert
this is a funny trick, and it looks saner than the more general $ * 
combinators.
i see many situations where i could use that to lift my own combinators,
or to replace the backticks (``) to lift the infix function.

thx
- marc


Gesendet: Freitag, 27. September 2013 um 21:51 Uhr
Von: Thiago Negri evoh...@gmail.com
An: Haskell-Cafe haskell-cafe@haskell.org
Betreff: [Haskell-cafe] Proposal: new function for lifting

Everybody is claiming that using lift is a bad thing.
So, I come to remedy this problem.
 

Stop lifting, start using shinny operators like this one:
 

    (^$) :: Monad m = m a - (a - b - c) - m b - m c
    (^$) = flip liftM2
 
Then you can do wonderful stuff and you will never read the four-letter word in 
your code again:
 
    \ Just 42 ^$(+)$ Nothing
    Nothing
    \ Just 10 ^$(+)$ Just 20
    Just 30
    \ let add = (+)
    \ Just 30 ^$ add $ Just 12
    Just 42
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative name for return

2013-08-06 Thread Marc Ziegert
very insightful, thx Jerzy.

imho, this is a good reason not to use already known words like 
lift,return,inject,pure etc. while still using the word Monad. (this is 
something that bothered me for years.)
no one -of those who say no one- does understand Monads because it does not 
explain itself nor suggest its utility, while the other words probably tend to 
cause a very false sense of understanding.

so, long talk few suggestions

if it should be about Monads as a concept, i'd suggest
1) unit and counit for Monads and Comonads. (this is my personal favorite 
choice, probably because i did learn to understand Monads by reading a paper 
about Comonads.)

if it should be more selfexplaining for the average coder, then
2) let,set,put,be,:= or return allowed only at end of script - use let 
anywhere else for ScriptLike (aka Monad)

as a strict version of return, i'd suggest something that may somehow fit into 
1 and 2:
3) eval = Control.Exception.evaluate :: a - IO a


regards
- marc




 Gesendet: Dienstag, 06. August 2013 um 11:43 Uhr
 Von: Jerzy Karczmarczuk jerzy.karczmarc...@unicaen.fr
 An: haskell-cafe@haskell.org
 Betreff: Re: [Haskell-cafe] Alternative name for return

 Le 06/08/2013 11:01, J. Stutterheim a écrit :
  ... So in reply to Jerzy, I do want to encourage the discussion in the 
  Noble Domain of Philosophy and I also want to repeat that I am not 
  proposing to change Haskell or Haskell libraries
 
 Jurriën, I taught Haskell for several years. I saw the disgraceful confusion 
 in heads of my students whose previous programming experience was based on 
 Python, and who learned Haskell and Java in parallel. So, I won't claim that 
 names are irrelevant. And return in particular.
 
 However, my personal philosophy is the following: accept the fact that 
 words in one language -- formal or natural -- mean something different than 
 in another one. [[In French the word file in computerese is queue in 
 English; this is in fact a French word meaning tail in English, and I have 
 several dozens of such examples... And so what?...]]
 
 It is good to choose consciously some good names while elaborating a 
 standard. But getting back to it after several years, is -- for me -- a waste 
 of time. This, unfortunately, pollutes the true philosophy as well. I believe 
 that at least 80% of the progress in the philosophy of religions belongs to 
 the linguistic domain.
 
 The anglosaxons corupted the word semantics, used in a pejorative sense: 
 discussion about superficialities, the words, not the concepts, while the 
 true semantics is about the true sense.
 
 So, sorry for being sarcastic, or even cynical in my previous post, but I 
 sincerely think that oldies are oldies, let them be, and work more on issues 
 that are still evolving.
 
 All the best.
 
 Jerzy
 
 
 
 ___
 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] Spam on list??

2013-07-02 Thread Marc Ziegert
i get this spam whenever anyone sends a mail to @eukor.com and this list at the 
same time.
i think that this kind of spam-bot sends to all recipients, not only to the 
person who sent it; but sends only if it sees @eukor.com in the TO: or CC: 
field.

so, if anyone knows a similar unsafeSpamBlocker, anyone of us might be able 
to disable one or both bots simply by sending a funny email (from a throw-away 
account because of side effects!!) to both email adresses - each twice to make 
it exponential. that would be the easiest pragmatic solution.

sadly, i don't know any other unsafeSpamBlocker than this; it is years ago that 
i saw one. i guess they do not survive more than a few weeks – at least not 
without beeing blacklisted automatically.

- marc


Gesendet: Montag, 01. Juli 2013 um 17:30 Uhr
Von: Brandon Allbery allber...@gmail.com
An: vlatko.ba...@gmail.com
Cc: Haskell-Cafe haskell-cafe@haskell.org
Betreff: Re: [Haskell-cafe] Spam on list??

On Mon, Jul 1, 2013 at 11:19 AM, Vlatko Basic 
vlatko.ba...@gmail.com[vlatko.ba...@gmail.com] wrote:

Anybody else getting this spam emails from j...@eukor.com[j...@eukor.com] every 
time a message is sent to Cafe?
 
Yes, and I'm hoping a list admin steps in soon.
 
The irony is, it's their *anti*spam filter. They decided to use one of those 
obnoxious whitelisting systems that requires all senders to register with it 
before it will pass on their mail... but didn't exclude mailing lists from 
this. Mailing lists, of course, can't authenticate, so they're sending all 
these image-heavy please whitelist yourself messages in Korean to the list 
submission address *and* not seeing any actual list traffic.
 
This is one of the reasons I sometimes wish that use of an active spam 
whitelist like this were grounds for disabling the user's email account. They 
can't even tell what kind of mess they're making.
 --

brandon s allbery kf8nh                               sine nomine associates
allber...@gmail.com[allber...@gmail.com]                                  
ballb...@sinenomine.net[ballb...@sinenomine.net]
unix, openafs, kerberos, infrastructure, xmonad        
http://sinenomine.net[http://sinenomine.net]

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


Re: [Haskell-cafe] Optimal line length for haskell

2012-10-29 Thread Marc Ziegert
O_o
Those are damn strange reasons to restrict oneself to 80 chars, iMho.

I tend to look at ONE file at a time, on one fullscreen widescreen.
100 chars per line is more or less normal; I have my vertical line limit marker 
set to 100, but only for layout-zen. My lines have sometimes 200 chars length, 
which causes the less important (long) code not to clutter my overview on the 
50 neighbouring lines (~10 functions overview on the left half of the screen). 
Otherwise, I'd use a browser/Haddock on one part of the screen just to see an 
overview of the code I'm writing.

I'm now wondering, whether this could have sth to do with my ADD, which I had 
the first 3 decades of my life (and without whiteboard). I think, I should try 
to code in a small narrow window of 1/4 of my screen, just to test whether that 
would (still) be a handicap.

Roman: academic background... Funny; my impression about this matter was from 
the other point of view: Short lines are good for diff/patch files.


Are there more people here with ADD (or ADD-history) and long-lines-disorder? 
Or is that just me?


- marc





 Original-Nachricht 
 Datum: Mon, 29 Oct 2012 11:32:29 -0400
 Von: MightyByte mightyb...@gmail.com
 An: Jake McArthur jake.mcart...@gmail.com
 CC: Haskell Cafe haskell-cafe@haskell.org
 Betreff: Re: [Haskell-cafe] Optimal line length for haskell

 I also stick to a pretty rigid 78 characters.  Doing so actually helps
 me fit more code onto my screen at a time because I usually have two
 or three columns of open files side by side.  I find that I need this
 more often than I need to see a single function on a page (thanks to
 Haskell's traditionally small functions).  But this works for single
 functions as well because I can open the same file in multiple columns
 at different locations in the file.
 
 The ideal line length for text layout is based on the physiology of
 the human eye… At normal reading distance the arc of the visual field
 is only a few inches – about the width of a well-designed column of
 text, or about 12 words per line. Research shows that reading slows
 and retention rates fall as line length begins to exceed the ideal
 width, because the reader then needs to use the muscles of the eye and
 neck to track from the end of one line to the beginning of the next
 line. If the eye must traverse great distances on the page, the reader
 is easily lost and must hunt for the beginning of the next line.
 Quantitative studies show that moderate line lengths significantly
 increase the legibility of text.
 Web Style Guide – Basic Design Principles for Creating Website
 Patrick J. Lynch and Sarah Horton
 2nd edition, page 97.
 
 On Mon, Oct 29, 2012 at 10:37 AM, Jake McArthur jake.mcart...@gmail.com
 wrote:
  I stick to 80 columns fairly rigidly. This is not only so that it fits
  into narrow windows, but also so that any two subexpressions in the
  same expression tend to be close together on my screen, which makes it
  easier for me to reason about it. If only it was easy for me to read
  and write code on a Hilbert curve... :)
 
  I don't think long lines indicate a design problem; it's solely a
  formatting thing.
 
  On Mon, Oct 29, 2012 at 7:50 AM, Rustom Mody rustompm...@gmail.com
 wrote:
  There was a recent discussion on the python list regarding maximum line
  length.
  It occured to me that beautiful haskell programs tend to be plump (ie
 have
  long lines) compared to other languages whose programs are 'skinnier'.
  My thoughts on this are at
  http://blog.languager.org/2012/10/layout-imperative-in-functional.html.
 
  Are there more striking examples than the lexer from the standard
 prelude?
  [Or any other thoughts/opinions :-) ]
 
  Thanks,
  Rusi
 
 
 
 
  ___
  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 mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments
(in deutsch: http://www.gerstbach.at/2004/ascii/)


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


Re: [Haskell-cafe] [Haskell] mapM with Traversables

2011-09-28 Thread Marc Ziegert
Hi Thomas,
this should be on the haskell-cafe or haskell-beginners mailing list. 
Haskell@... is mainly for announcements.


You have:
 f :: Monad m =
  a - m b
 Data.Traversable.mapM :: (Monad m, Traversable t) =
  (a - m b) - t a - m (t b)

So, if you define g with
 g a = do Data.Traversable.mapM f a
 or in short
 g = Data.Traversable.mapM f
, then the type will be
 g :: (Monad m, Traversable t) =
  t a - m (t b)
instead of
 g :: [a] - m (Seq b)
.

Try using ghci to find these things out. It helps to get not confused with the 
types.


Besides the missing Monad context, g misses a generic way to convert between 
different Traversables, which does not exist. You can only convert from any 
Traversable (imagine a Tree) toList; not all Traversables have a fromList 
function.
For conversion, you might want to use Foldable and Monoid, fold to untangle and 
mappend to recombine; but any specific fromList function will surely  be more 
efficient.

Regards
- Marc



 Original-Nachricht 
 Datum: Wed, 28 Sep 2011 17:27:58 -0600
 Von: thomas burt thedwa...@gmail.com
 An: hask...@haskell.org
 Betreff: [Haskell] mapM with Traversables

 Hi -
 
 I have a function, f :: Monad m = a - m b, as well as a list of a's.
 I'd
 like to produce a sequence (Data.Sequence) of b's, given the a's:
 
 g :: [a] - m (Seq b)
 g a = do Data.Traversable.mapM f a   -- type error!
 
 I see that Data.Traversable.mapM f a doesn't work... is this like asking
 the compiler to infer the cons/append operation from the type signature of
 g?
 
 Do I need to write my own function that explicitly calls the append
 functions from Data.Sequence or can I do something else that would work
 for
 any g :: Traversable t, Traversable u = t a - m (u b) given f :: a -
 m
 b?
 
 Thanks for any comments!
 Thomas

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


Re: [Haskell-cafe] Endian conversion

2005-10-05 Thread Marc Ziegert
you are right, that pice of code is ugly. i would write sth simmilar 
(Int32-[Word8]) like you did, iff it should be able to cross-compile or do not 
need to be fast or should not need TH.
well, i think, in the case of joel's project the last sentence means ..., iff 
true or true or undefined.

is there any architecture with sth like 0xaabbccdd-bb aa dd cc, ghc (or any 
other haskell-compiler) runs on? (i did know, that such architectures exist.)

- marc


Udo Stenzel wrote:
  Why don't you pull out 4 bytes and assemble them manually?
 
 To that I'd like to add a snippet from NewBinary itself:
 
 | instance Binary Word32 where
 |   put_ h w = do
 | putByte h (fromIntegral (w `shiftR` 24))
 | putByte h (fromIntegral ((w `shiftR` 16) .. 0xff))
 | putByte h (fromIntegral ((w `shiftR` 8)  .. 0xff))
 | putByte h (fromIntegral (w .. 0xff))
 |   get h = do
 | w1 - getWord8 h
 | w2 - getWord8 h
 | w3 - getWord8 h
 | w4 - getWord8 h
 | return $! ((fromIntegral w1 `shiftL` 24) .|.
 |(fromIntegral w2 `shiftL` 16) .|.
 |(fromIntegral w3 `shiftL`  8) .|.
 |(fromIntegral w4))
 
 This obviously writes a Word32 in big endian format, also known as
 network byte order, and doesn't care how the host platform stores
 integers.  No need for `hton' and `ntoh'.  To convert it to write little
 endian, just copy it and reorder some lines.  (But I think, writing LE
 integers with no good reason and without an enclosing protocol that
 explicitly declares them (like IIOP) is a bad idea.)
 
 [Which reminds me, has anyone ever tried implementing a Corba ORB in
 Haskell?  There's a binding to MICO, but that just adds to the uglyness
 of MICO and does Haskell a bit of injustice...]
 
 
  Well, I liked that bit of Template Haskell code that Marc sent. I'm  
  now stuck trying to adapt it to read Storables :-).
 
 I don't.  It's complex machinery, it's ugly, it solves a problem that
 doesn't even exist and it solves it incompletely.  It will determine the
 byte order of the host system, not of the target, which fails when
 cross-compiling, and it doesn't work on machines with little endian
 words and big endian long words (yes, this has been seen in the wild,
 though might be extinct these days).  Use it only if You Know What You
 Are Doing, have a performance problem and also know that writing
 integers en bloc would help with it.
 
 
  I could read a FastString from a socket since it has IO methods but I  
  don't know how to convert the FS into a pointer suitable for  
  Storable. So much to learn :-).
 
 useAsCString might be your friend.  But so might be (fold (:) []).
 
 
 Udo.
 -- 
 The greatest dangers to liberty lurk in insidious encroachment by men
 of zeal, well-meaning but without understanding.
   -- Brandeis
 
 ___
 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] Endian conversion

2005-10-03 Thread Marc Ziegert
well, fastest conversion to compute could be an assembler-command, but if we 
don't use that, it could be converted via Foreign.Storable and sth like the 
following: (i did not test it, and i hope, TH works like this...)

data (Integral a) = BigEndian a = BigEndian a deriving (Eq,Ord,Enum,...)
be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) 
:: Bool
instance (Storable a) = Storable (BigEndian a) where
 sizeOf (BigEndian a) = sizeOf a
 alignment (BigEndian a) = alignment a
 peek = if be then peek0 else peekR
  where
   peek0 (BigEndian a) = peek a
   peekR = peekByteOff `flip` 0
 peekByteOff = if be then peekByteOff0 else peekByteOffR
  where
   peekByteOff0 (BigEndian a) = peekByteOff a
   peekByteOffR (BigEndian a) i = peekByteOff a (sizeOf a - 1 - i)
...poke...

- marc


Tomasz Zielonka wrote:
 On 10/3/05, Joel Reymont [EMAIL PROTECTED] wrote:
 
  Folks,
 
  Are there any endian conversion routines for Haskell? I'm looking to
  build binary packets on top of NewBinary.Binary but my data is coming
  in little-endian whereas I'll need to send it out big endian.
 
 
 From your question I assume you want functions like htonl / ntohl.
 I think the cleanest approach is to always have yours Ints, etc in host
 order, and place
 the endianness stuff in serialization / deserialization code, ie. on the
 Number - Byte
 sequence boundary.
 
 Having htonl/ntohl as pure functions in Haskell would be a bit ugly, because
 they would be defined differently on different platforms, and putting them
 in the
 IO monad would make them barely usable.
 
 Best regards
 Tomasz
 
 ___
 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] Endian conversion

2005-10-03 Thread Marc Ziegert
for just making IO and a little bit-conversion, i would use c++ or even c. for 
such a problem you have to be near the machine, not necessarily near 
mathematical abstraction.
there exist assembler-commands to flip endians of register-values, so i would 
just search in /usr/include/*/* for a platform independent c-function, and 
either pipe a proxy through such a little prog, or patch an existing proxy, 
like tinyproxy.
of course, if you want to make more than just a proxy, or if you want to play 
with different languages, be welcome to use haskell. but remind, it is not easy 
to use high-developed-mars-rover-technology to replace a shovel for playing 
with sand at the beach.

- marc

Joel Reymont wrote:
 Well, I'm looking for suggestions on how to implement this. I'll  
 basically get a chunk of data from the socket that will have things  
 little-endian and will need to send out a chunk that will have the  
 numbers big-endian.
 
 This is a proxy server that does binary protocol conversion. It's a  
 breeze to implement in Erlang but I'm partial to Haskell and trying  
 to apply it to all sorts of problems. Please, let me know if this is  
 not the type of problem to apply Haskell to ;-).
 
  Thanks, Joel
 
 On Oct 3, 2005, at 8:35 AM, Tomasz Zielonka wrote:
 
  Having htonl/ntohl as pure functions in Haskell would be a bit  
  ugly, because
  they would be defined differently on different platforms, and  
  putting them in the
  IO monad would make them barely usable.
 
 --
 http://wagerlabs.com/idealab
 
 
 
 
 
 ___
 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] Endian conversion

2005-10-03 Thread Marc Ziegert
nice project. (except that winonly-closedsource-thing. my condolence.)
on which platform are you programming? mac? linux-ppc?

i see that you understood most of that code. 
big-endian-test: the number 1234 has two ends (like a sausage), the end with 
the 1 is the big end (1000), the 4 is the little one. if you save he number 1 
as int in little endian, then you write the bytes 01 00 00 00, and in big 
endian it is 00 00 00 01. so, if you read the first char, then it will either 
be ==1 (little) or /=1 (big).
to write that LittleEndian stuff, you only need to replace Big with Little and 
if be then with if not be then. it is the question wether to use he 
function xyz0(derived) or xyzR(reverse order of bytes). i hope, that the 
compiler optimizes if True away.

to use the Storables, read the docu about the libs(functions)
Network.Socket(sendBufTo)
Foreign.Marshal.Utils(with)
Foreign.Storable(peekThis,peekThat)

you just need to read LittleEndian CInt, remove that 
LittleEndian-constructor, work with that CInt, put the 
BigEndian-constructor at that CInt, write it...

maybe you need to convert LE and BE enums, too. use (toEnum . fromEnum) to 
convert between any enum and CInt.

good n8.
- marc


Joel Reymont wrote:
 Well, I liked that bit of Template Haskell code that Marc sent. I'm  
 now stuck trying to adapt it to read Storables :-).
 
 It seems, on a second glance, that there's not that much to adapt. If  
 I read Marc's code correctly it derives Storable and uses the peek,  
 etc. methods to swap bytes around. Which means to me that so long as  
 the byte swapping methods are implemented and I try to store a  
 BigEndian or LittleEndian it would be stored correctly for me.
 
 Is this so?
 
 To recap, I'm trying to read binary packets from a socket and the  
 first thing I do is read the packet length. I then need to read the  
 packet body where the numbers are little or big endian. After  
 processing the packet I need to write it out and the numbers again  
 could be little or big endian.
 
 I could read a FastString from a socket since it has IO methods but I  
 don't know how to convert the FS into a pointer suitable for  
 Storable. So much to learn :-).
 
  Thanks, Joel
 
 On Oct 3, 2005, at 9:33 PM, Udo Stenzel wrote:
 
  Why don't you pull out 4 bytes and assemble them manually?  Three
  shifts, logical ors and fromIntegrals aren't that much of a burden  
  after
  all.
 
 --
 http://wagerlabs.com/idealab
 
 
 
 
 
 ___
 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] Basic type classing question.

2005-09-21 Thread Marc Ziegert
maybe, i completely missunderstand you. please, could you program your example 
in another language than haskell, one you know better?
i'm not sure -- did you try to define variables instead of types?

data Employee = Emp
data Department = Dept
translated to c++ this means sth like
typedef void Employee;
typedef void Department;

did you want sth like ...?
data Employee = Emp [(String,Either String Int)]
emp1 :: Employee
emp1=Emp [(Name,Left Karl Ranseier),(Identifier,Right 7),(Address,Left 
Graveyard 13)]

-marc


Karl Grapone wrote:
 Hi,
 
 I've just started learning Haskell, and I must admit I'm finding it a
 bit hard to get my head around the typing system...
 
 If I wanted to represent Employees and Departments in a Haskell
 program I could use data declarations like so:
 data Employee = Emp ...
 data Department = Dept ...
 
 This seems limited in (at least) two ways:
 I can't dynamically add fields to an employee or department, and
 once I pull a field out of an instance I lose type information.
 
 
 What I want to be able to do is add and remove fields while the system
 is running, I suppose via hs-plugins, and I should be prevented from,
 for example, accidentally taking an employees first name and using it
 as a departments address.
 
 My first attempt was the following, which isn't even valid and doesn't
 appear to buy me much anyway.
 
 class DataContainer c
 
 class DataContainer c = DataField f c a where
   extract :: f - a
   apply :: (a - a - a) - f - f - f
 
 data DataContainer c = Field c a = Fld c a
 instance DataField Field c a where
   extract (Fld _ a) = a
   apply f (Fld c a1) (Fld _ a2) = Fld c (f a1 a2)
 
 
 data Employee = Emp
 instance DataContainer Employee
 
 data Department = Dept
 instance DataContainer Department
 
 type EmployeeName = Field Employee String
 type EmployeeAddress = Field Employee String
 type EmployeeIdentifier = Field Employee Integer
 type DepartmentAddress = Field Department String
 type DepartmentIdentifier = Field Department Integer
 ...
 
 
 The 'DataField instance Field' declaration gives kind errors regarding
 how many type arguments Field is applied to.  I don't claim to
 understand kinds at this point.
 Even if it did work, apply doesn't appear to force the arguments to be
 of the same type, and the declared type synonyms aren't enough to
 prevent me getting employee names and addresses confused.
 
 Is there a correct way to express what I'm trying to do?  Or is it a
 bad idea to start with?
 
 Thanks
 Karl
 ___
 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] Newbie syntax question

2005-09-18 Thread Marc Ziegert
  map (foo 5) my_list_of_lists_of_doubles

 1. map (flip foo 5) my_list_of_lists_of_doubles
 2. map (`foo` 5) my_list_of_lists_of_doubles
 3. map (\x-foo x 5) my_list_of_lists_of_doubles
 4. [foo x 5 | x - my_list_of_lists_of_doubles]

well, i've followed this discussion a while, but i did not see that solution i 
used for years. (i like solution 2, never thought of it before.)
my solution is a variant of 1, that makes the reading a little bit easier -- at 
least to me.

5. map (foo `flip` 5) my_list_of_lists_of_doubles

the `flip` shows the position behind foo, where to put the parameter. its a 
pitty that it only works if there is only one parameter behind `flip`.

so, with abcd :: a-b-c-d-x
abcd a b `flip` d :: c-x
works, but
abcd a `flip`  c d :: b-x
does not.

experimenting with Data.Arrow, it could look like:
(abcd a  ($ c)  ($ d)) :: b-x
or with a flip-arrow combination:
(abcd a `flip` c)  ($ d) :: b-x
so, instead of hacking with arrows on it, i prefer solutions 3 and 4 whenever 5 
does not work.

- marc

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