Re: [Haskell-cafe] Re: XML (HXML) parsing :: GHC 6.8.3 space leak from 2000

2008-09-23 Thread Marc A. Ziegert
  
  -- Lazily build a tree out of a sequence of tree-building events
  build :: [TreeEvent] - ([UnconsumedEvent], [Tree String])
  build (Start str : es) =
  let (es', subnodes) = build es
  (spill, siblings) = build es'
  in (spill, (Tree str subnodes : siblings))
  build (Leaf str : es) =
  let (spill, siblings) = build es
  in (spill, Tree str [] : siblings)
  build (Stop : es) = (es, [])
  build [] = ([], [])
 
 [skip]
 
  We don't know of a good way to fix this problem.  I'm going to record 
  this example in a ticket for future reference, though.
 
 Simon,
 
 is there a way, perhaps, to rewrite this expression to avoid leaks?
 An ad-hoc will do, perhaps split in two modules to avoid intramodular
 optimizations?
 
 -- 
 Lev Walkin

finally... there is a way! :D

hmm... this was a nice puzzle ;)

i've tried several times (and hours!) to implement a Continuation (not monad) 
based solution, but finally i developed this tricky but elegant foldr 
solution...
i built the parser around this type:
  type FoldR_Builder = (TreeEvent,[UnconsumedEvent]) - [Either 
[UnconsumedEvent] (Tree String)] - [Either [UnconsumedEvent] (Tree String)]

it is based on the following thought:
the tuple
  (rs,ps)::([Rest],[Processed]) -- with the restriction, which forces the list 
ps to be processed entirely before rs.
is equipollent to
  (fmap Right ps++[Left rs])::[Either [Rest] Processed]
, but the latter is easier to handle ...at least if you can't trust the GC.


- marc

---example_context_free_grammar_parser.hs--
module Main where

import Data.List

data Tree a = Tree a [Tree a] deriving Show

data TreeEvent = Start String   -- Branch off a new subtree
| Stop  -- Stop branching and return 1 level
| Leaf String   -- A simple leaf without children
deriving Show

main = print . snd . build $ Start top : cycle [Leaf sub]
--main = print . snd . build $ [Leaf bla,Leaf bla,Start S(,Leaf 
bli,Start T(,Leaf blu,Stop,Stop,Leaf bla]

type UnconsumedEvent = TreeEvent-- Alias for program documentation



build :: [TreeEvent] - ([UnconsumedEvent], [Tree String])
build tes = let (ts_,ue_,_) = splitAtLeftDefault [] $ foldr builder [] 
[(te,ue)|ue@(te:_)-tails tes] in (ue_,ts_)
--  
^
-- a little change (bugfix?) to the space leaking solution...
-- [Stop,Leaf x]  now evaluates to  ([Stop,Leaf x],[])  instead of  ([Leaf 
x],[])
-- like this:   build ue@(Stop:_) = (ue,[])
-- instead of:  build (Stop : es) = (es,[])

type FoldR_Builder = (TreeEvent,[UnconsumedEvent]) - [Either [UnconsumedEvent] 
(Tree String)] - [Either [UnconsumedEvent] (Tree String)]
builder :: FoldR_Builder
builder (Stop,ue) euts = (Left ue:euts)
builder (Leaf str,_) euts = (Right (Tree str []):euts)
builder (Start str,_) euts = let (sub,_,euts') = splitAtLeftDefault [] euts in 
(Right (Tree str sub):euts')


-- default value is needed iff the list is finite and contains no (Left _).
splitAtLeftDefault :: a - [Either a b] - ([b],a,[Either a b])
splitAtLeftDefault a0 [] = ([],a0,[])
splitAtLeftDefault a0 (Right b:xs) = let (bs,a,es) = splitAtLeftDefault a0 xs 
in (b:bs,a,es)
splitAtLeftDefault _ (Left a:xs) = ([],a,xs)















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


Re: [Haskell-cafe] Haskell Related Reading

2008-06-29 Thread Marc A. Ziegert
i think, you are looking for this paper:
Functional programming with bananas, lenses, envelopes and barbed wire
http://citeseer.ist.psu.edu/meijer91functional.html

atm, the link is broken or server offline. so here is another reference...
http://doc.utwente.nl/56289/

the paper is pretty cool, but it has nothing to do with arrows, monads or 
haskell-arrows.
for those, i don't know any paper.

- marc



Am Samstag, 28. Juni 2008 schrieb Darrin Thompson:
 I have a trip coming up and might have some reading time. I was hoping to
 get through some of the classics, bananas and lenses, the essence, etc.
 
 So I have a few questions:
 
 Bananas and lenses et. al. uses some notation that I don't understand right
 out of the gate. Is there a good primer on whatever that brand of double
 bars and arrows means?
 
 The essense of functional programming looks good, I could understand it when
 I skimmed it but can I print it out on US letter? The PDF at citeseer was
 aligned badly. (Essece seemed like a fabulous intro or chapter 2 on getting
 used to monads. Better than most stuff on the web. Funny that...)
 
 I'm also interested in FRP as it might relate to web programming. Anyone
 have a recommendation?
 
 --
 Darrin
 




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


Re: [Haskell-cafe] GADT rhymes with cat

2008-03-16 Thread Marc A. Ziegert
GADTs always reminds me of the japanese word gattsu.
ガッツ == ga-tsu-tsu == gattsu, spoken somehow like gah-t--ts... followed 
by a half spoken english u (second half).
gattsu means in english guts.
that in mind, i was just GADDing in StarDict, which translates gatsugatsu 
with burning with desire for something, greedily.

hm. that explains how excited some people are about this extension. guts are 
important.

- marc


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


Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Marc A. Ziegert
Am Freitag, 21. Dezember 2007 schrieb Justin Bailey:
 Given this function:
 
   dropTest n = head . drop n $ [1..]
 
 I get a stack overflow when n is greater than ~ 550,000 . Is that
 inevitable behavior for large n? Is there a better way to do it?
 
 Justin

[1..] equals [1, (1)+1, (1+1)+1, (1+1+1)+1, (1+1+1+1)+1, ...] where the 
brackets are a reference to the previous entry in the list.
so, if you want to reach the nth element in [1..], then the garbage collector 
automagically collects the unused list entries... but there are no unused.

[1..]!!10 = ((1)+1)+1)+1)+1)+1)+1)+1)+1)+1)+1
now, that one long formula needs to be completely build in the stack prior to 
evaluation.
to prevent this, each value has to be evaluated before stepping deeper into the 
list. i.e. like with this bang pattern:

let ((!x):xs)!!!i = case i of {0-x;_-xs!!!pred i} in [1..]!!!10

or simply like this trick:
[1..maxBound]!!10
this causes every single entry to be checked against the list-end-condition, 
just before the calculation of the next list entry.


- marc



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


Re: [Haskell-cafe] MonadFix

2007-12-18 Thread Marc A. Ziegert
Am Dienstag, 18. Dezember 2007 schrieb Joost Behrends:
snip
fix f is the least fixed point of the function f, i.e. the least defined x
 such that f x = x.
 
 What does least mean here ? There is nothing said about x being a variable 
 of
 an instance of Ord. And why fix has not the type a - (a - a) - a, means: 
 How
 can i provide a starting point of the iteration x == f x == f (f x) == 
 ...?  
 
snip

the starting point is undefined.
the ordering of functions is is_subset_of.


a more detailed explanation:

a function A - B is a subset of the cartesian product A x B, where for 
each element in A there is not more than one element in B.
subsets are partially ordered. the empty set (the function const undefined or 
simply undefined) is the lowest subset, and AxB is the largest (but in most 
cases not a function).
the function f0 (_::a) = (undefined::b) is the lowest subset.
the function f1 ('x'::a) = (5+fromEnum 'x'::b) is larger than f0.
the function f1' ('y'::a) = (7::b) is larger than f0, and not equal (neither 
equal, nor lower, nor larger) to f1.
the function f2 (c::a) | isUpper c = (5 + fromEnum c::b) is larger than f1, 
and not equal (neither equal, nor lower, nor larger) to f1'.
the function fn (c::a) | True = (5 + fromEnum c::b) is one maximal defined 
function: it is defined on every input parameter.

now, the fix function takes a function construct_f::(a-a)-(a-a) and 
calculates first (construct_f undefined) :: (a-a). undefined :: (a-a) 
equals f0, the lowest function/element, but it is not a fixpoint. construct_f 
undefined is a bit more defined
construct_f . construct_f . construct_f . construct_f . ... (oo times) $ 
undefined is the largest thing you can get this way, it does not need to be 
defined everywhere, but it is a fixpoint. there may be larger fixpoints, but no 
lower.

example:

fix construct_f
 where construct_f f = \x - (if x==0 then 42 else f (x-1))

look at construct_f undefined: it constructs a function which is defined on 
the input x==0; otherwise it tries to evaluate undefined (x-1), which is 
completely undefined.
look at construct_f $ construct_f undefined: it constructs a function which 
is defined on the input x==0 and x==1.

fix cf = cf (fix cf) is the fixpoint function, and with this...
fix construct_f constructs a function which is defined on all inputs x=0, 
but not on inputs x0. this function is one fixpoint (the least one) of 
construct_f.
another function is a fixpoint of construct_f: \x-42. but this is a larger 
function than the above fixpoint, so this is not the LEAST FIXPOINT; the above 
one is.
you can test, whether it is a fixpoint: construct_f (\x-42) == (\x-if x==0 
then 42 else (\x-42)(x-1)) == (\x-if x==0 then 42 else 42) == (\x-42)
exercise1: construct_f (\x-if x=0 then 42 else 23) == ...?
exercise2: construct_f (\x-if x=0 then 42 else undefined) == ...?

another example: lists.

fix (\fibs-1:1:zipWith (+) fibs (tail fibs))



i hope to have helped.
- marc





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


Re: [Haskell-cafe] GUI

2007-12-12 Thread Marc A. Ziegert
Am Mittwoch, 12. Dezember 2007 schrieb Miguel Mitrofanov:
 Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's  
 not native on my Mac; some Mac users don't install it and almost  
 all Mac users don't always run it.

the problem is Apple. if you want to have a native gui on OSX then you are 
either nearly stuck to Objective-C or to obsolete gui libraries.
i'm not a mac user, but i know one who is; he told me.
on osx there are two main gui apis: carbon and cocoa.

carbon is obsolete, but it partially runs on osx -- it is not 64bit compatible.
http://en.wikipedia.org/wiki/Carbon_%28API%29

cocoa is the newer one, which every mac user likes.
AFAIK there is no C backend to that api, so you will have to develop a C 
backend first and then the haskell (or gtk2) wrapper.
there are some bindings for other languages, i.e. C#, but no C.
http://en.wikipedia.org/wiki/Carbon_%28API%29

if you are able to code objective-c and know how to access cocoa using c, 
please help those gtk developers to port gtk2 to native OSX.
it will then automagically work with gtk2hs.

- marc


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


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-11 Thread Marc A. Ziegert
i did just read the haskell description from galois [1]. i like
 1) ...enabling much higher coding efficiency, in addition to formalisms that 
greatly ease verification.
 2) All programming languages suffer from a semantic gap:...

maybe we could compose sth similar to 1) to introduce static typed functional 
programming, and to 2) to introduce some strange new buzzwords coming with 
haskell.
i'm sure, there will be no problem in using scary words, iff we introduce them 
as easy-to-handle master solutions to all incurable programming diseases. ;)



...imho the present slogan [2] is not that bad, too.

- marc

[1] http://www.galois.com/methods.php
[2] http://haskell.org/haskellwiki/?title=Haskelloldid=17367



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


Re: [Haskell-cafe] Style

2007-08-24 Thread Marc A. Ziegert

Marc A. Ziegert [EMAIL PROTECTED]

 tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
   where fives = iterate (*5) 1
 tm_improved_v1 n = sum . takeWhile (0) $ iterate (div `flip` 5) (div n 5)
 tm_fastestIMHO n = let m=div n 5 in if m5 then m else m+tm_fastestIMHO m


Henning Thielemann [EMAIL PROTECTED]

 tm4 = sum . takeWhile(0) . tail . iterate (flip div 5)


Bjorn Bringert [EMAIL PROTECTED]

 tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n]
 

Arie Groeneveld [EMAIL PROTECTED]

 tm = sum . takeWhile(0) . iterate f . f
where f = flip div 5
 tm1 n = sum . takeWhile(0) . map (div n . (5^)) $ [1..]
 tm2 n = sum . takeWhile(0) . map (div n) $ iterate ((*)5) 5
 tm3 = sum . takeWhile(0) . flip map (iterate ((*)5) 5) . div


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


Re: [Haskell-cafe] Style

2007-08-24 Thread Marc A. Ziegert
whops... i did check it, but
that was a copypaste mistake.

buggy:
 tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
   where fives = iterate (*5) 1

should be:
 tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
   where fives = iterate (*5) 5

- marc


Am Freitag, 24. August 2007 schrieben Sie:
 Hi Marc
 
 First off, thanks for your reply.
  tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
 where fives = iterate (*5) 1
 Did you check this one? IMHO I think it's producing the 'wrong' answer.
 
 *Main tm_parallelizable_v1 100
 124
 (0.00 secs, 0 bytes)
 
 *Main tm 100
 24
 (0.00 secs, 0 bytes)
 
 If comparing the result to the other variants is accepted as a sort
 of proof. ;-)
  
 But calculating the number of trailing zero's of n! is a matter of
 counting powers of five in the factorized n!: f.e.:
 
 10! = 1 2 3 2^2 5 2*3 7 2^3 3^2 2*5
 -- 5^2 -- picking up enough powers of 2 -- (2*5)^2 = 100
 
 So you will have to correct your 'fives' to f.e.
 
 fives = tail $ iterate (*5) 1
 
 
 
 Regards
 
 
 @@i
  
 
 




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


Re: [Haskell-cafe] #haskell irc channel reaches 400 users

2007-08-22 Thread Marc A. Ziegert
i interpret it as this:

all [ usage x  usage y || fun_to_talk_about x  fun_to_talk_about y
| let lang=[minBound .. maxBound] -- C++,Haskell,Java,etc.
, x-lang
, y-lang
, irc_channel_users x  irc_channel_users y 
]


- marc


Am Dienstag, 21. August 2007 schrieb Albert Y. C. Lai:
 Andrew Coppin wrote:
  ...does this mean Haskell is officially harder to understand than Lisp, 
  Java, Perl and O'Caml? :-}
  
  (OTOH, does this mean Haskell is easier to understand than PHP or C++?)
 
 Or, Haskell is the easiest to understand of them all.
 
 Reason: Extremely large channel means so hard to understand that many 
 people want help. Extremely small channel means so hard to understand 
 that few people show interest. The middle-sized channel sits at the 
 sweet spot.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 




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


[Haskell-cafe] howto install ghc-6.7.* ?

2007-08-11 Thread Marc A. Ziegert
i just don't get it.
please, can anybody explaim me how to do that?
i tried it the last few days with ghc-6.7.20070807, ghc-6.7.20070809, and 
ghc-6.7.20070810.
it always results in a broken library (without Prelude):

# ghc-pkg list
/usr/local/lib/ghc-6.7.20070810/package.conf:
{ghc-6.7.20070810}, rts-1.0

i did this on my gentoo-i386-box (pretty old, takes 1h for quick build, 3.5h 
without mk/build.mk):

T=20070810
tar xjf ghc-6.7.$T-src.tar.bz2 
tar xjf ghc-6.7.$T-src-extralibs.tar.bz2 
cd ghc-6.7.$T
(
#echo BuildFlavour = quick
#cat mk/build.mk.sample
echo HADDOCK_DOCS = YES
)  mk/build.mk
./configure  ( time nice -n 19 make all install )


those extralibs seem to be installed in
 /usr/local/lib/ghc-6.7.20070810/lib/
but registered in
 ghc-6.7.20070810/driver/package.conf.inplace
instead of
 /usr/local/lib/ghc-6.7.20070810/package.conf
.


- marc


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


Re: [Haskell-cafe] creating graphics the functional way

2007-08-06 Thread Marc A. Ziegert
Am Montag, 6. August 2007 00:48 schrieb Frank Buss:
 I've created a small program to compose images with combinators:
 
 http://www.frank-buss.de/haskell/OlympicRings.hs.txt
 
...
 look very smooth. And it is very slow, it needs about 40 seconds on my
computer to calculate the image. Using parametrized combinators sounds like
...


in that source file, you define Size and Pixel as structs of Integers. that 
are neither unsigned chars (8_bit) nor ints (32-64_bit) nor floats (32_bit) but 
an artificial oo_bit int (1 int + list of bytes).
i'm sure you will gain a speedup by redefining these structs. i.e. use Float or 
Int instead of Integer; see Data.Int and Data.Word for more alternatives.

- marc



[code snippet from source file]
-- image size
data Size = Size { width :: Integer, height :: Integer }
deriving (Eq, Ord, Show, Read)

-- RGB components for an image pixel
data Pixel = Pixel { r :: Integer, g :: Integer, b :: Integer }
deriving (Eq, Ord, Show, Read)

-- helper functions for saving bytes
writeByte byte = putWord8 (fromIntegral byte)
writeBytes bytes = mapM_ putWord8 bytes

-- binary instance for saving Pixels
instance Binary Pixel where
put (Pixel r g b) = do
writeByte b
writeByte g
writeByte r
get = error Pixel get not supported

[/code]



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


Re: [Haskell-cafe] Exiting GLUT application

2007-07-31 Thread Marc A. Ziegert
in old glut, the main loop was the core of the single threaded program. exiting 
it did mean to exit the program completely.
in freeglut, you have alternatives. but for compatibility, it defaults to the 
old behaviour.

http://haskell.org/ghc/docs/latest/html/libraries/GLUT/Graphics-UI-GLUT-Begin.html#v%3AExit

- marc


Am Dienstag, 31. Juli 2007 19:16 schrieb Dave Tapley:
 Hi everyone, I have the following skeleton GLUT code:
 
  import Graphics.UI.GLUT
  main = do
  getArgsAndInitialize
  createWindow 
  mainLoop
 
 It loads into both hugs and ghci fine and when 'main' is evaluated an
 empty window opens as expected.
 However when closing the window (clicking the window manager's x
 button) both hugs and ghci exit with the window, as opposed to
 returning to the the 'Main' prompt.
 
 I suspect I need some callback to exit the GUI cleanly?
 
 Cheers,
 Dave
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


Re: [Haskell-cafe] GHC and GLUT

2007-07-25 Thread Marc A. Ziegert
to replace only libglut.so is not enough. if i understand you correctly, you 
changed the backend without the API. (you need .h at compiletime, .a (an 
archive of .o files) when you link everything to an executable, and .so at 
runtime.)
my libglut installation comes with...

/usr/lib/libglut.a
/usr/lib/libglut.la
/usr/lib/libglut.so.3.8.0
/usr/lib/libglut.so.3 (link to .3.8.0)
/usr/lib/libglut.so   (link to .3.8.0)
/usr/include/GL/freeglut.h
/usr/include/GL/glut.h
/usr/include/GL/freeglut_ext.h
/usr/include/GL/freeglut_std.h

i guess, you have to recompile Graphics.UI.GLUT, too.

- marc


Am Mittwoch, 25. Juli 2007 05:27 schrieb Paul L:
 I wonder if anybody has experience with the GLUT library that GHC
 currently supports? I was trying to use freeglut because I need the
 actionOnWindowClose function. GHC documentation seems to indicate it's
 possible to do this, but my effort isn't successful.
 
 I even replaced the system-wide libglut.so with the new libglut.so
 that comes with freeglut installation, but GHC still won't recognize
 it's now freeglut and I still can't use the actionOnWindowClose
 function.
 
 This is on Linux, and I've not tried Windows. Do I need to compile GHC
 myself in order to enable freeglut support? Any help is greatly
 appreciately!
 
 Regards,
 Paul L
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


Re: [Haskell-cafe] Weird ghci behaviour?

2007-07-21 Thread Marc A. Ziegert
 This is ghc 6.6. Anyone else seeing this?
not here.

what do these output:
ghc --version
and
ghci --version
? are they different?

besides that.. why do you use 6.6? may it bee.. is your Unix-like OS sth 
between OSX and linux? (i remenber there exists a Gnu/Darwin package manager 
without the (faster bootstrapping) ghc-6.6.1)

- marc



Am Freitag, 20. Juli 2007 23:12 schrieb Dan Piponi:
 On Unix-like OSes:
 
 If I run ghc test.hs and then run ghci test.hs, ghci fails to load
 up my code. I have to touch test.hs and then run ghci. I can
 understand ghci refusing to recompile something it thinks it has
 already compiled. But it appears to refuse to load it into an
 interactive session - which is less useful. In fact, removing test.hi
 makes ghci work again.
 
 This is ghc 6.6. Anyone else seeing this?
 --
 Dan
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-10 Thread Marc A. Ziegert
Am Dienstag, 10. Juli 2007 00:25 schrieb Albert Y. C. Lai:
 http://xkcd.com/c287.html

 It disappoints me that there is no solution if each item is used at most 
 once. However, do change the code to allow multiple uses, then there are 
 many solutions.

i see only two solutions.

let menu = [215, 275, 335, 355, 420, 580]
let run x menu = [[c]|c-menu,c==x]++[c:cs|c-menu,cx,cs-run (x-c) (dropWhile 
(/=c) menu)]
run 1505 menu

-
[[215,215,215,215,215,215,215],[215,355,355,580]]



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


Re: [Haskell-cafe] Haskell's partial application (not currying!) versus Business Objects Gem Cutter's burning

2007-07-04 Thread Marc A. Ziegert
exercise done. :D
there is still a problem with the functional dependencies. see last line of 
code.
- marc

Am Mittwoch, 4. Juli 2007 14:22 schrieb Conor McBride:
{? * 10 + ?} 4 2 = 42
   
 http://hackage.haskell.org/trac/haskell-prime/wiki/FlexiblePartialApplication

 
 (3) Exercise for readers:
 
implement constructors
  P v  for embedding pure values v
  Ofor holes
  f :$ a   for application, left-associative
and an interpreting function
  emmental
such that
  emmental (P (+) :$ (P (*) :$ O :$ P 10) :$ O) 4 2 = 42
 
 I think the question of whether to support linear abstractions other  
 than of
 an argument suffix is an interesting one. The flip answer is a bad  
 answer;
 lambda abstraction is a good answer, but sometimes feels too heavy  
 for this
 job. I really don't have a strong opinion about whether it's worth  
 supporting
 a lighter notation for the linear case, but I thought I'd at least  
 try to
 inform the debate.
 
 All the best
 
 Conor
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
{-# OPTIONS  -fglasgow-exts -farrows -fbang-patterns -fno-full-laziness -funbox-strict-fields  -fallow-undecidable-instances #-}
{-# PACKAGE ghc-6.6 #-}
{-# LANGUAGE ExistentialQuantification #-}

module Main where

--import Control.Arrow
--import Data.Array as Array
--import Data.Array.ST as STArray
--import Data.Array.Unboxed as UArray
--import Data.Map as Map
--import Data.Set as Set
--import Data.List as List
--import Data.Queue
--import Data.Sequence as Seq
--import Data.IntSet as IntSet
--import Data.IntMap as IntMap
--import Data.Maybe
--import Data.Bits (xor)
--import Data.Word
--import Data.Int
--import Control.Monad
--import Control.Arrow
--import Control.Monad.State
--import Control.Monad.Writer
--import Data.Foldable (foldrM)
--import Control.Applicative
--import Data.Traversable
--import System.Posix
--import System.IO.Unsafe
--import Data.Graph.Inductive as Gr hiding (())
--import qualified Data.Graph.Inductive.Example as Example
--import Data.Graph.Inductive.Query.BFS
--import Control.Monad.ST.Strict
--import Data.STRef
--import System.Random
--import Data.Ratio
--import System.Exit
--import MonadLib



{-

   implement constructors
 P v  for embedding pure values v
 Ofor holes
 f :$ a   for application, left-associative
   and an interpreting function
 emmental
   such that
 emmental (P (+) :$ (P (*) :$ O :$ P 10) :$ O) 4 2 = 42

-}
type ONE = SUCC ZERO
type TWO = SUCC ONE

data ZERO
data NAT n = SUCC n

class NAT n where
  nat :: n - Int
instance NAT ZERO where
  nat _ = 0
instance NAT n = NAT (SUCC n)  where
  nat _ = succ $ nat (undefined::n)


newtype HOLE a = HOLE a

class NAT n = UNHOLE n h f | n h - f where
  unhole :: n - h - f
instance UNHOLE ZERO (P v) v where
  unhole _ (P v) = v
instance (NAT n , UNHOLE n f g) = UNHOLE (SUCC n) ((HOLE a)-f) (a-g) where
  unhole _ f = unhole (undefined::n) . f . HOLE

data P v = P v
data O = O
data (:$) f a = f :$ a

infixl 8 :$

{-
class PLUS a b c | a b - c where
instance PLUS ZERO b b where
instance (PLUS a b c) = PLUS (SUCC a) b (SUCC c) where

class COUNT a n | a - n where
  countH :: a - n
  countH _ = undefined
instance COUNT (P v) ZERO where
instance COUNT O ONE where
instance (COUNT f nf,COUNT a na,PLUS nf na nfa) = COUNT (f :$ a) (nfa) where
-}

class EmToH e n h | e - n h where
  emToH :: e - h
instance EmToH (P v) ZERO v where
  emToH (P v) = v
instance EmToH O ONE (HOLE h-h) where
  emToH O (HOLE h) = h
instance (EmToH f nf f',EmToH a na a',ApplyH nf f' na a' nfa fa) = EmToH (f :$ a) nfa fa where
  emToH (f :$ a) = applyH (undefined::(nf,na)) (emToH f) (emToH a)

class ApplyH nf f na a nfa fa | nf f na a - nfa fa where
  applyH :: (nf,na) - f - a - fa
instance ApplyH ZERO (a-fa) ZERO a ZERO fa where
  applyH _ f a = f a
instance (ApplyH ZERO f na a na fa) = ApplyH ZERO f (SUCC na) (HOLE h-a) (SUCC na) (HOLE h-fa) where
  applyH _ f a h@(HOLE _) = applyH (undefined::(ZERO,na))f (a h)
instance (ApplyH nf f na a nfa fa) = ApplyH (SUCC nf) (HOLE h-f) na a (SUCC nfa) (HOLE h-fa) where
  applyH _ f a h@(HOLE _) = applyH (undefined::(nf,na)) (f h) a

class UnH n f r | n f - r where
  unH :: n - f - r
instance UnH ZERO f f where
  unH _ = id
instance (UnH n f r) = UnH (SUCC n) (HOLE h-f) (h-r) where
  unH _ f h = unH (undefined::n) $ f (HOLE h)


class Emmental e f | e - f where
  emmental :: e - f

instance (EmToH e n h, UnH n h r) = Emmental e r where
  emmental = unH (undefined::n) . emToH








main :: IO ()
--main = print $ emmental (P (+) :$ (P (*) :$ O :$ P 10) :$ O) 4 2
main = print $ emmental (P ((+)::Int-Int-Int) :$ (P ((*)::Int-Int-Int) :$ O :$ P (10::Int)) :$ O) (4::Int) (2::Int)





pgpCnHKLE0z6g.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] found monad in a comic

2007-06-14 Thread Marc A. Ziegert
well, i see sth like this:

data IceCream = EmptyCone | Vanilla | Strawberry | Wasabi | ...
data Hypothetical a = ...

instance Monad Hypothetical where -- one Functor and two Natural 
Transformations:
   fmap :: (a - b) - (Hypothetical a - Hypothetical b)
   return :: a - Hypothetical a
   join :: Hypothetical (Hypothetical a) - Hypothetical a

and this is the eye opener:
knife = join!
there is no unsafePerformIO-alike
coreturn :: Hypothetical a - a.
that belongs to CoMonads.

you can actually do the same trick like in the comic in RealWorld:
fmap:
 whatever you can do in the real world, that can be done in the Hypothetical 
world, too.
return:
 into an Hypothetical world you can imagine/return everything from the real 
world ...even whole Hypothetical worlds (return (return Wasabi)) and 
world-cutting knifes (return join).
join:
 but the knife/join will never be a .../coreturn, a bridge from any 
Hypothetical world into the RealWorld.
that is what i call a monad.

- marc

P.S.:
i do not understand what the others are interpreting, maybe it is too high for 
me to see any connection between the comic and kripke semantics, higher order 
physics, the different worlds we live in...
for me it is just a little monad like Id without runId.


Am Donnerstag, 14. Juni 2007 21:10 schrieb Albert Y. C. Lai:
 Andrew Coppin wrote:
  ...is everybody else looking at a different web page to me? *blinks*
 
 Everybody is interpreting it differently. (As usual.)
 
 I see an unsafePerformIO. :)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


[Haskell-cafe] found monad in a comic

2007-06-11 Thread Marc A. Ziegert

http://xkcd.com/c248.html
( join /= coreturn )

IMHO this could be a beautiful and easy way to explain monads.
comments?

- marc




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


Re: [Haskell-cafe] What puts False before True?

2007-05-30 Thread Marc A. Ziegert
Am Donnerstag, 31. Mai 2007 05:52 schrieb PR Stanley:
 What is the basic philosophy for Bool being a member of Ord?
you can do sth like

Data.Set.fromList [minBound .. maxBound] :: Data.Set.Set Bool

 What justifies False  True?
in most interpretations this equals:

False == 0
True == 1
and == (*)
or == max
not == (1 -)
a `xor` b == (a + b) `mod` 2

and not this:

False == 1
True == 0
and == max
or == (*)
not == (1 -)
a `xor` b == (a + b) `mod` 2


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


Re: [Haskell-cafe] Memoization

2007-05-27 Thread Marc A. Ziegert
you may want to use a container like Array or Map.
most times i use an Array myself to speed things up like this.
with Map it will either be a bit tricky or you'll need to use an unsafeIO hack.
here are some functions that may help you. my favorites are Array and MapMealey.
- marc


memoizeArrayUnsafe :: (Ix i) = (i,i) - (i-e) - (i-e)
memoizeArrayUnsafe r f = (Data.Array.!) $ Data.Array.listArray r $ fmap f $ 
Data.Ix.range r
memoizeArray :: (Ix i) = (i,i) - (i-e) - (i-e)
memoizeArray r f i = if Data.Ix.inRange r i then memoizeArrayUnsafe r f i else 
f i


data Mealey i o = Mealey { runMealey :: i - (o,Mealey i o) }
memoizeMapMealey :: (Ord k) = (k-a) - (Mealey k a)
memoizeMapMealey f = Mealey (fm Data.Map.empty) where 
fm m k = case Data.Map.lookup m k of
(Just a) - (a,Mealey . fm $ m)
Nothing - let a = f k in (a,Mealey . fm $ Data.Map.insert k a 
$ m)

memoizeMapST :: (Ord k) = (k-ST s a) - ST s (k-ST s a)
memoizeMapST f = do
r - newSTRef (Data.Map.empty)
return $ \k - do
m - readSTRef r
case Data.Map.lookup m k of
(Just a) - return a
Nothing - do
a - f k
writeSTRef r $ Data.Map.insert k a m
return a


or with inelegant unsafe hacks you get more elegant interfaces:


memoizeMapUnsafeIO :: (Ord k) = (k-IO a) - (k-a)
memoizeMapUnsafeIO f = unsafePerformIO $ do
r - newIORef (Data.Map.empty)
return $ \k - unsafePerformIO $ do
m - readIORef r
case Data.Map.lookup m k of
(Just a) - return a
Nothing - do
a - f k
writeIORef r $ Data.Map.insert k a m
return a

memoizeMap :: (Ord k) = (k-a) - (k-a)
memoizeMap f = memoizeMapUnsafeIO (return . f)
memoizeMap f = runST $ do
f' - memoizeMapST (return . f)
return $ runST . unsafeIOToST . unsafeSTToIO . f'


Am Sonntag, 27. Mai 2007 04:34 schrieb Mark Engelberg:
 I'd like to write a memoization utility.  Ideally, it would look
 something like this:
 
 memoize :: (a-b) - (a-b)
 
 memoize f gives you back a function that maintains a cache of
 previously computed values, so that subsequent calls with the same
 input will be faster.
 
 I've searched the web for memoization examples in Haskell, and all the
 examples use the trick of storing cached values in a lazy list.  This
 only works for certain types of functions, and I'm looking for a more
 general solution.
 
 In other languages, one would maintain the cache in some sort of
 mutable map.  Even better, in many languages you can rebind the name
 of the function to the memoized version, so recursive functions can be
 memoized without altering the body of the function.
 
 I don't see any elegant way to do this in Haskell, and I'm doubting
 its possible.  Can someone prove me wrong?
 
 --Mark
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


Re: [Haskell-cafe] how can I select all the 3-element-combination out of a list efficiently

2007-05-20 Thread Marc A. Ziegert

with which model in Combinatorics in mind do you want that function? with or 
without repetition?

http://en.wikipedia.org/wiki/Combinatorics#Permutation_with_repetitionthe 
order matters and each object can be chosen more than once
http://en.wikipedia.org/wiki/Combinatorics#Permutation_without_repetition the 
order matters and each object can be chosen only once
http://en.wikipedia.org/wiki/Combinatorics#Combination_without_repetition the 
order does not matter and each object can be chosen only once
http://en.wikipedia.org/wiki/Combinatorics#Combination_with_repetitionthe 
order does not matter and each object can be chosen more than once




--
import Data.List

perm3_with_rep,perm3_without_rep,comb3_with_rep,comb3_without_rep :: [a] - 
[(a, a, a)]
perm3_with_repes = [(x,y,z)|x-es,y-es,z-es]
perm3_without_rep es = [(x,y,z)|let it s=zip s $ zipWith (++) (inits s) (tail $ 
tails s),(x,xr)-it es,(y,yr)-it xr,z-yr]
comb3_with_repes = [(x,y,z)|let it=init.tails,xs@(x:_)-it es,ys@(y:_)-it 
xs,z-ys]
comb3_without_rep es = [(x,y,z)|let it=init.tails,(x:xr)-it es,(y:yr)-it 
xr,z-yr]

comb3_to_perm3 :: [(a, a, a)] - [(a, a, a)]
comb3_to_perm3 xyz = concat[perm_without_rep [x,y,z]|(x,y,z)-xyz]
--



- marc


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


Re: [Haskell-cafe] Haskell: the Craft of Functional Programming

2007-05-20 Thread Marc A. Ziegert

i don't know where my copy is or who it has, for years.
but i remember one bad thing... either i missread the following (my english was 
not that good) or it is a bug in the book:

(in the first chapter, i guess)
if you have the function
 sqr x = x*x
then haskell does reduce the term
 sqr (1+2)
first to
 (1+2) * (1+2)
and then to
 3 * (1+2)

that hurts.


the only thing i still remember to have learnt from that book is the good style 
of programming, which is very well explained.
(only one due to my Prelude and other Hugs-Library source reading/studying 
before.)
well, that alone is worth enough to read that book. even though it is plain old 
haskell98 without those gorgeous libs and without -fglasgow-exts.

- marc



Am Montag, 21. Mai 2007 01:46 schrieb PR Stanley:
 Hi
 I've acquired a copy of the above title but it requires a lot of 
 transcription work. So, I thought I'd first ensure it's worth the 
 time and effort. This edition was published in 1999.
 All Opinions on the text, good or bad, would be very welcome.
 Thanks,
 Paul
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


[Haskell-cafe] runST $ return () /= runST (return ()) ??

2007-03-24 Thread Marc A. Ziegert
hi!

i've just discovered this strange behaviour of existential quantifiers with 
runST:

---
Prelude Control.Monad.ST :t runST (return ())
runST (return ()) :: ()

Prelude Control.Monad.ST :t runST $ (return ())
interactive:1:9:
Couldn't match expected type `forall s. ST s a'
   against inferred type `m ()'
In the second argument of `($)', namely `(return ())'

Prelude Control.Monad.ST
---


the same with id runST undefined.
is this a bug or an unsolved problem?
i'm not sure wheather it is a part of the wanted feature of runST's type 
definition.

i did not find any discussions about this.
can anyone enlighten me, please?

- marc



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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Marc A. Ziegert
Am Samstag, 6. Januar 2007 05:12 schrieb Brian Hurt:
 Even better, if I define:
 
 nth 0 (x:_) = Just x
 nth i (_:xs) = if i  0 then Nothing else nth (i-1) xs
 nth i [] = Nothing
 
 makelist i = i `seq` i : (makelist (i+1))
 
 nth 1000 (makelist 1)
 

Hi Brian.
i just like to mention another tricky solution:
you can apply seq in such a way to the list, so that each element will be 
evaluated before advancing deeper into the list.


ghci -fglasgow-exts -fbang-patterns

Prelude :t foldr
foldr :: forall a b. (a - b - b) - b - [a] - b

Prelude let strict = foldr (\x xs -x `seq` (x:xs)) []
Prelude let strict = foldr (\(!x) xs - (x:xs)) [] --  using bang patterns 
instead, this is easier to read
Prelude let strict = foldr ((:) $!) [] --  or complete 
pointfree
Prelude let lazy   = foldr ((:) $) []
Prelude :t strict
strict :: forall a. [a] - [a]

Prelude lazy [1..] !! 100
*** Exception: stack overflow
Prelude strict [1..] !! 100
101



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


Re: [Haskell-cafe] Showing the 1 element tuple

2006-12-19 Thread Marc A. Ziegert
 A weird question, what does the 1 element tuple look like?

there is one in Control.Monad.Identity:
 Identity 1
i miss the short version
 newtype Id x = x


writing (1,) is not that well defined; how do you want to use its constructor 
alone?
writing (1;) may be the solution, i think. (;) could be the constructor.
does anyone know, how ; could cause any problems?
if i am not mistaken, (do return 1 ; return 2;) should be the same like ((do 
return 1 ; return 2);).

- marc


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


Re: [Haskell-cafe] Getting my feet wet - small browser game

2006-12-18 Thread Marc A. Ziegert
 Comments and suggestions welcome :-)
hi Joachim.

i have some suggestions:

apache:
use fastcgi instead of hacking an own http-server.
http://www.cs.chalmers.se/~bringert/darcs/haskell-fastcgi/doc/
http://www.cs.chalmers.se/~bringert/darcs/cgi-compat/doc/

server:
there are virtual linux servers out there, free to rent.
some of them are even cheaper than the power-usage of one's old pc (at least 
compared to speed).
if you intend to write a game for thousands of users, who play it 24/7, then it 
may be comfortable to rent one.
(friends of me rented one.)

software upgrades:
use Read/Show classes instead of Foreign.Marshal,
and combine them with version counting data-structures:

[code]
data MyData = V1 String deriving (Show,Read)
read_v1 :: MyData - String
-
data MyData = V1 String
| V2 [String] deriving (Show,Read) 
read_v1 :: MyData - String
read_v2 :: MyData - [String]
-
data MyData = V1 String
| V2 [String]
| V3 [(String,Int)] deriving (Show,Read) 
-- obsolete: read_v1 :: MyData - String
read_v2 :: MyData - [String]
read_v3 :: MyData - [(String,Int)]
[/code]


i've thought about writing a browsergame in haskel, too;
but atm, i have no time for (writing) games.

- marc




Am Montag, 18. Dezember 2006 12:30 schrieb Joachim Durchholz:
 OK, after years of looking and discussing and doing HSoE exercises, I
 have finally decided that Haskell is far enough into practical
 usefulness that I should give it a try in a real project.
 
 The basic idea is a browser game - this touches all the potentially hard
 issues without miring me too deeply in target platform details.
 
 I'd like to lay out my plans here and ask how they are going to work
 out, and take advice.
 
 THE PLAN
 
 I'll start with
 http://haskell.org/haskellwiki/How_to_write_a_Haskell_program and get a
 toolchain together. I haven't decides which compiler (interpreter?) to
 choose; I'll probably go for the one that give the least amount of trouble.
 
 Next would be library selection. I'm willing to undergo some modest
 amount of hassle here, since I don't expect all libraries that I need to 
 be mature yet.
 
 My preliminary plan is to split the application into a central world 
 simulation process, and satellite processes that accept HTTP requests, 
 feed them into the simulation, read back the results, and generate the 
 response HTML.
 The interface between simulation and satellite is:
 * Satellites can read a snapshot of the game data.
 * Satellites cannot directly write game data.
What they can do is to post commands to a blackboard, which are marked
as no more updatable as soon as the simulation starts executing
them.
 
 I expect the simulation and the satellites to be separate OS processes, 
 so I'll need a way to marshall command and game data between processes.
 The simulation will have to store its entire state to disk, too - in 
 theory, it could run forever and never write to disk (and I don't need a 
 database, too), but in practice, I have to plan for the occasional reboot.
 Since the server will be running Apache for other purposes anyway, and I 
 don't want to force the players to use a URL with a port number, I think 
 I'll set up Apache so that it proxies game-related URLs to the Haskell 
 software. I just hope that Apache doesn't incur much overhead in that mode.
 
 I have no idea how to organize software upgrades. The satellites are 
 easy, but how do I make sure that revision N+1 of the simulation can 
 read the marshalled data from revision N?
 
 The final software should be efficient. Ideally, the satellites are able 
 to saturate the network card of today's typical cheap rootserver if the 
 simulation is a no-op.
 I have two data points for a typical cheap rootserver:
 * 100 MBit/s Ethernet, 256 MB RAM, 1.2 GHz Celeron (~3 years old)
 * 1 GBit/s Ethernet, 1 GB RAM, 2.2 GHz Athlon (current)
 Of course, not needing an RDBMS will give the system a head start 
 efficiency-wise.
 
 
 Comments and suggestions welcome :-)
 
 Regards,
 Jo
 
 ___
 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] Why is this array use wrong?

2006-12-16 Thread Marc A. Ziegert
b needs a type.

[code]
Prelude Data.Array.IArray :t array
array :: (Ix i, IArray a e) = (i, i) - [(i, e)] - a i e
Prelude Data.Array.IArray let b = array (1,33) [(i,False) | i - [1..33]] :: 
Array Int Bool
Prelude Data.Array.IArray :t b
b :: Array Int Bool
Prelude Data.Array.IArray b
array (1,33) 
[(1,False),(2,False),(3,False),(4,False),(5,False),(6,False),(7,False),(8,False),(9,False),(10,False),(11,False),(12,False),(13,False),(14,False),(15,False),(16,False),(17,False),(18,False),(19,False),(20,False),(21,False),(22,False),(23,False),(24,False),(25,False),(26,False),(27,False),(28,False),(29,False),(30,False),(31,False),(32,False),(33,False)]
Prelude Data.Array.IArray 
[/code]

the error said:
 No instance for (IArray ...)
 arising from use of `array'

the unspecified type of b did not had this instance;
but now it has the type Array --and with that type the needed instance, too.

- marc



Am Samstag, 16. Dezember 2006 12:56 schrieb Maurí­cio:
Hi,
 
I'm trying this in ghci:
 
 let b = array (1,33) [(i,False) | i - [1..33]]
 
 after :m Data.Array.IArray. It gives me that error message:
 
 interactive:1:8:
  No instance for (IArray a Bool)
arising from use of `array' at interactive:1:8-12
  Probable fix: add an instance declaration for (IArray a Bool)
  In the definition of `b': b = array (1, 33) ([(i, False) | i - [1 
 .. 33]])
 
Why?
 
Thanks,
Maurício
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] don't: a 'do' for comonads?

2006-11-09 Thread Marc A. Ziegert
don't :: a
don't = error D'oh!

- marc



Am Donnerstag, 9. November 2006 04:47 schrieb Donald Bruce Stewart:
 As seen on #haskell, from an idea by Malcolm,
 
 14:42  ?let top'n'tail = (pre++) . (++/pre) 
 14:42  lambdabot Defined.
 14:43  dons  L.top'n'tail foo me now
 14:43  lambdabot  prefoo me now/pre
 14:43  mauke that reminds me, haskell needs don't
 14:43  dons yes!
 14:44  pkhuong- mm. the opposite of do, eh? do for comonads? :)
 
 So now a prize to the person who comes up with the best use for the
 identifier:
 
 don't :: ?
 
 -- Don
 ___
 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] throwing sugar into the void.

2006-05-06 Thread Marc A. Ziegert
[EMAIL PROTECTED]

I'd like to hear some comments about the following ideas; maybe they are 
someway obsolete or even useless nonsense.

A few days ago, I thought about abstracting the instance of an object away, 
like used in Foreign.Storable.sizeOf::(Storable a)=a-Int, where only the type 
of an object is used.
The problem with the function sizeOf is, that the result should be constant per 
definition(*), but how can we make the compiler know this?

(*)
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Foreign-Storable.html#v%3AsizeOf
 sizeOf::a-Int
 Computes the storage requirements (in bytes) of the argument. The value 
 of the argument is not used. 

So I thought we may need a new (abstract) datatype to wrap the type of an 
object, just to contain no dynamic data:

data Type a
typeOf :: a - Type a
typeOf = undefined
#define TYPE(a) (undefined::Type (a))
...
sizeOf :: (Storable a) = Type a - Int

Maybe this is a little bit too ugly and cumbersomely, just to make sizeOf 
constant.
This version of sizeOf is not really comfortable anymore; but it isn't 
comfortable to write (undefined::a), too.
To be able to write (::a) instead, would be really nice, IMHO; but how about 
(_::a)?

--
trying to be equivocating
 undefined is another way to implement ...nothing.
/trying to be equivocating
More comfortable would it be to write a single symbol instead of the long word 
undefined:

_ :: a
_ = undefined

Using _ as a function should not be such a problem: it cannot be mixed with 
the joker _ as parameter.
To define this function may be a problem: It needs a compiler-patch to allow 
this, ATM.

--
By the way, this symbol is not used at type-level... How about praefix/postfix 
operators instead of only infix?

-- praefix
newtype BigLambda a = BigLambda a
(/\) :: _ - a - BigLambda a
/\ a = BigLambda a

-- postfix
newtype Lifted a = Lifted a
(!^) :: a - _ - Lifted a
a !^ = Lifted a

May this be confusing? Or even impossible? Am I insane?
Well, I don't know how hard it would be to implement those language features. I 
would not like to make anyone implement all this, if it is only a 
niceToHave-butIDontUseIt, like the implicit parameters feature.


- marc

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


Re: [Haskell-cafe] [Newbie] Why or why not haskell ?

2005-12-10 Thread Marc A. Ziegert
hi Christophe.

 In terms of speed, is haskell good enough ?

in some cases, optimized haskell may even be faster than C. (that depends on 
your C-programming skills. i.e. function-inlining will speed C up, too.) how 
possible? look at the mangler:
http://www.haskell.org/ghc/docs/6.4.1/html/building/sec-porting-ghc.html#sec-mangler

there were discussions about the efficiency of some compilers and their 
technics.
http://www.mail-archive.com/glasgow-haskell-users@haskell.org/msg08729.html

networking:
hm. sorry, don't know. ...look at the libraries.


my personal experience with other languages:
- ada
nada.
- erlang
nice. easy to learn, functional, multi-threaded, and more elegant than lisp.
see http://en.wikipedia.org/wiki/Wings_3D as example program.
- clisp or scheme
forget those lisp languages. boooring. brackets everywhere. lisp was one of the 
first (was the first?) functional languages. if you like to experiment with the 
lambda-calculus, this is the perfect language.
well, you still should learn it, because it is too easy to learn, and it is 
still used. maybe you will meet that language in the future. spend some time 
into learning it, before you learn haskell. some hours should be enough.
http://en.wikipedia.org/wiki/Lisp_programming_language
suggestion: how about learning haskell and lisp at the same time? write an 
lisp-interpreter as your first haskell-project. ;)
- haskell
it is like the c++stl of functional languages, just higher. it is 
meta-programming. think about it as the tool-language, that replaces thousands 
of code-monkeys.
and it will be really easy, after you started to think in haskell. that could 
take some time, so don't give up.
it has three giant disadvantages:
1.) you do not feel the need for learning other languages anymore.
2.) waiting for a new ghc release, with new never-thought-of-before high-level 
language extensions, can make you crazy.
3.) the industry prefers vc++.net, java#, vb-excel-script, php4iexplorer and 
other bug-friendly (most times proprietary and/or incompatible) languages 
instead of haskell.

to start with a functional language, read about the lambda-calculus. functional 
languages depend on it.
http://en.wikipedia.org/wiki/Lambda_calculus

to learn haskell, continue with...
http://en.wikipedia.org/wiki/Haskell_programming_language
http://haskell.org/hawiki/ (especially about monads and arrows)
...and reading the library.
http://haskell.org/ghc/docs/latest/html/libraries/index.html

as gui library, i preferr...
http://www.haskell.org/gtk2hs/

- marc

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


Re: [Haskell-cafe] Confused about Cyclic struture

2005-07-07 Thread Marc A. Ziegert
well, it is a little bit tricky.
you know, imps do not always make what you want.

 imp_creates x = x `knot` imp x
 where knot = (:)

imagine the following:
you pull a foulard out of your  sleeve,

 foulard : sleeve
 where sleeve = imp_creates foulard

and pull

 foulard : foulard : sleeve
 where sleeve = imp_creates foulard

and pull.

 foulard : foulard : foulard : sleeve
 where sleeve = imp_creates foulard

you will waste more and more space, maybe your storage will swell to discworld.
this is recursion, but not a cyclic structure.
on the other hand:

 serviette_ring
 where serviette_ring = foulard `knot` serviette_ring

you will pull one single foulard through that thing.

 x@( foulard `knot` serviette_ring )
 where knot = (:)
   serviette_ring = x

and then there is a knot with the beginnig of the same thing you pulled out 
before.

 beginning@( foulard `knot` beginning )
 where knot = (:)

if you pull more and more, you will get the same foulard again and again.
you do not need an imp to produce more and more foulards, because this knot 
closes the ring.
so, you will never fill the room just by pulling, because this is a nice little 
cyclic structure.


- marc




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


Re: [Haskell-cafe] pair (f,g) x = (f x, g x)?

2005-07-02 Thread Marc A. Ziegert
'.' is not always a namespace-separator like '::','.','-' in c++ or '.' in 
java.
it is used as an operator, too.
 (.) :: (b-c) - (a-b) - (a-c)
 (f . g) x = f (g x)

remember the types of fst and snd:
 fst :: (a,b)-a
 snd :: (a,b)-b
so the function (.) combines
 square :: Int - Int
with fst to
 (square . fst) :: (Int,b) - Int
 
the same with toUpper:
 (Char.toUpper . snd) :: (a,Char) - Char

so you have with 'pair (f,g) x = (f x,g x)':

 pair (square . fst,Char.toUpper . snd) (2,'a')
==
 ((square . fst) (2,'a'), (Char.toUpper . snd) (2,'a')) 
==
 ( square (fst(2,'a')), Char.toUpper (snd(2,'a')) )
==
 ( square 2 , Char.toUpper 'a' )
==
 (4,'A')


- marc



Am Samstag, 2. Juli 2005 08:32 schrieb wenduan:
 I came across a haskell function on a book defined as following:
 
 pair :: (a - b,a - c) - a - (b,c)
 pair (f,g) x = (f x,g x)
 
 I thought x would only math a single argument like 'a', 1, etc,but 
 it turned out that it would match something else, for example, a pair as 
 below:
 
 square x = x*x
 
 pair (square.fst,Char.toUpper.snd) (2,'a')
 (4,'A')
 
 The type declaration of  pair is what confused me,
 pair :: (a - b,a - c) - a - (b,c),it says this function will take a 
 pair of functions which have types of a-b,a-c,which I would take as 
 these two functions must have argument of the same type, which is a,and 
 I didn't think it would work on pairs as in the above instance,but 
 surprisingly it did,can anybody enlighten me?
 
 -- 
 X.W.D
 
 ___
 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