Re: re[Haskell-cafe] cord update

2010-09-14 Thread -Steffen
While we are at it using Semantic Editor Combinators (sec on hackage): {-# LANGUAGE TemplateHaskell #-} module T where import Data.SemanticEditors data MyRecord = MyRecord { field1 :: String, field2 :: Int, field3 :: Bool } deriving(Show) mkEditors [''MyRecord] editRecord str =

Re: Re[Haskell-cafe] targeting Haskell compiler to embedded/hardware

2010-09-29 Thread -Steffen
If you are really interested in embedded realtime code you may want to have a look at the timber language[1] or bit-c[2]. Another very interesting project is this[3] developing a new Haskell like language called Habit for systems programming. There are also some great papers about systems

[Haskell-cafe] Re: EDSL for Makefile

2010-10-03 Thread steffen
If you don't want to mention r1 explicitly, but want to refer to target, sources and such only a monadic approach (e.g. Reader Monad) might be what you want. On Oct 3, 6:14 am, C K Kashyap ckkash...@gmail.com wrote: Thanks Emil ... yeah, that works...I was wondering what I could do to not

[Haskell-cafe] Re: EDSL for Makefile

2010-10-04 Thread steffen
Telling from the video and the slide, Neil's make system is actually really cool. Indeed something I would really enjoy to use. It support dynamic and static dependency tracking (more or less) out of the box (by storing dependencies in a database file). So you use want and need to tell the system

[Haskell-cafe] Re: Lazy evaluation from Why Functional programming matters

2010-10-05 Thread steffen
Don't be to disappointed. One can always kinda fake lazy evaluation using mutable cells. But not that elegantly. In the example given above, all being used is iterators as streams... this can also be expressed using lazy lists, true. But one big difference between e.g. lazy lists and iterators is,

[Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread steffen
A slightly different suggestion from Simon PJ and myself (we agreed on something syntax-related :-) is the following:  \case 1 - f        2 - g ...  \case { 1 - f; 2 - g } +1 I like this because it has exactly the same properties of Max's case-of, but is shorter and still reads

[Haskell-cafe] Re: EDSL for Makefile

2010-10-06 Thread steffen
calls the shell command echo to print some lines) you can try in ghci by typing runTest test... [1] http://gist.github.com/614246 On 3 Okt., 16:56, C K Kashyap ckkash...@gmail.com wrote: On Sun, Oct 3, 2010 at 5:22 PM, steffen steffen.sier...@googlemail.com wrote: If you don't want to mention r1

[Haskell-cafe] Re: dph question

2010-10-15 Thread steffen
I trying to learn a bit about data parallel haskell, and started from the wiki page here:http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell. Two questions: The examples express the dot product as: dotp_double xs ys = sumP [:x *

[Haskell-cafe] Re: Map constructor in a DSL

2010-10-26 Thread steffen
Hi, I think you may want to over think your types again. Especially your Evaluator-Monad, and maybe your Map constructor. The Problem is, due to your use of Either and the need for evalObs to finally transform from Obs [a] type to Evaluator [a] you will end up in another Monad for Either:

[Haskell-cafe] Re: Map constructor in a DSL

2010-10-26 Thread steffen
) (sequence = return . sequence) On 27 Okt., 06:12, steffen steffen.sier...@googlemail.com wrote: Hi, I think you may want to over think your types again. Especially your Evaluator-Monad, and maybe your Map constructor. The Problem is, due to your use of Either and the need for evalObs to finally

[Haskell-cafe] Re: Map constructor in a DSL

2010-10-28 Thread steffen
and deduce Map from it. But maybe I have to add a List constructor for that. But in the suggestions from Ryan and Brandon I don't understand why I should add an extra type parameter and what it is! Steffen: Wow nice. I'll integrate that ;) I'm also looking at the Atom's DSL to get inspiration

[Haskell-cafe] Re: State nested structures

2010-10-29 Thread steffen
Horribly enough this one seems to work... mapOnBofA :: SB a - SA a mapOnBofA mf = get = \st@(A {b=temp}) -                let (ans,temp2) = runState mf temp                in put (st { b=temp2}) return ans There is nothing horrible about that. You just run a new isolated computation in

[Haskell-cafe] Re: State nested structures

2010-10-29 Thread steffen
29, 2010 at 6:19 PM, steffen steffen.sier...@googlemail.comwrote: Horribly enough this one seems to work... mapOnBofA :: SB a - SA a mapOnBofA mf = get = \st@(A {b=temp}) -                let (ans,temp2) = runState mf temp                in put (st { b=temp2}) return ans

[Haskell-cafe] Re: State nested structures

2010-10-29 Thread steffen
29, 2010 at 6:19 PM, steffen steffen.sier...@googlemail.comwrote: Horribly enough this one seems to work... mapOnBofA :: SB a - SA a mapOnBofA mf = get = \st@(A {b=temp}) -                let (ans,temp2) = runState mf temp                in put (st { b=temp2}) return ans

Re: Fwd: [Haskell-cafe] DSL libraries

2010-11-07 Thread steffen
...@gmail.com wrote: Nobody had the compilation messages I had? -- Forwarded message -- From: Dupont Corentin corentin.dup...@gmail.com Date: Tue, Nov 2, 2010 at 2:30 PM Subject: [Haskell-cafe] DSL libraries (Was: Map constructor in a DSL) To: steffen steffen.sier

[Haskell-cafe] Re: How to generalize executing a series of commands, based on a list?

2010-11-18 Thread steffen
1. Write one routine, which does all the work for just one command. 2. use sequence or mapM, mapM_ from Control.Monad (depending on your needs), to apply your function to a list of commands accumulating results you may want to process the output of sequence or use the WriterT Monad

[Haskell-cafe] Re: Manatee Video.

2010-11-30 Thread steffen
Hi Andy, Can you please do something about the sound track? Loads of people are not able to view your video, because the used content/sound track is not available in every country... meaning youtube prohibits viewing your video. On 28 Nov., 17:30, Andy Stewart lazycat.mana...@gmail.com wrote:

Re: [Haskell-cafe] Manatee Video.

2010-11-30 Thread steffen
the launcher thing, Manatee modes and window management into one application. Maybe by making Manatee an opt in module for xmonad?!? Would this be possible? On 30 Nov., 15:10, Andy Stewart lazycat.mana...@gmail.com wrote: steffen steffen.sier...@googlemail.com writes: Hi Andy, Can you please

Re: [Haskell-cafe] Managing multiple installations of GHC

2010-12-02 Thread steffen
On Dec 1, 2010, at 8:38 PM, Antoine Latter wrote: If you're doing user installations of packages with 'cabal-install' it will take care of everything - all of the things that it installs are in per-GHC-version directories. ... Except for the haddock documentation that cabal-install

Re: [Haskell-cafe] Tracing applied functions

2011-01-25 Thread steffen
did you try Debug.Trace? http://haskell.org/ghc/docs/latest/html/libraries/base/Debug-Trace.html On Jan 25, 3:39 am, Aaron Gray aaronngray.li...@gmail.com wrote: On 25 January 2011 02:12, Ivan Lazar Miljenovic ivan.miljeno...@gmail.comwrote: On 25 January 2011 12:05, Aaron Gray

Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-10 Thread steffen
just fine, but I will keep a copy of crt1.10.5.o before upgrading to Xcode 4 just in case and report any findings. - Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-10 Thread steffen
Questions: 1. How did you install ghc-7? Using a binary package? The one for leopard or snow leopard? 2. Which compiler flags did you use? Does it work with another backend? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-11 Thread steffen
/Versions/Current/usr/share/doc/ghc/html/libraries/ghc-7.0.2/src/Config.html So we either have to copy or symling /Developer-old/SDKs/MacOSX10.5.sdk to /Developer/SDKs or someone is going to recompile ghc with snow leopard only in mind. - Steffen

Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-12 Thread steffen
There is no SDK for older Mac OS X Releases in XCode 4, but for iPhone... Not even in the Resources/Packages. Indeed Apple did remove support for older Systems then snow leopard in its new development tools. For that reason and problems with no support of IB Plugins one is encouraged not to

Re: [Haskell-cafe] Automatic Reference Counting

2011-07-05 Thread steffen
retain/release for them by yourself, but by convention you don't do so...), but the counter may be accessed directly in memory. That's why ARC (if you follow Apple's conventions about object ownership) can be much more efficient than the current implementation. - Steffen

Re: [Haskell-cafe] Improvements to Vim Haskell Syntax file - Is anyone the maintainer?

2011-09-08 Thread steffen
github mirror or hackage). As I've made some extensive changes I will continue maintaining the syntax file (unless someone else really wants to do it...), but I'd prefer it to be a haskell-comunity project so other people can join in easily and propose changes. - Steffen

[Haskell-cafe] ghc overlapping instances

2007-12-04 Thread Steffen Mazanek
ghc such that it accepts such an instance? In hugs -98 +o is enough. I have tried -XOverlappingInstances, -XFlexibleInstances and also -XIncoherentInstances, however I still got an overlapping instances error for this declaration. Regards, Steffen

Re: [Haskell-cafe] ghc overlapping instances

2007-12-05 Thread Steffen Mazanek
::Program main = mapM_ (\(s,a) - putStrLn s a) [(flowchart construct and parse, test prop_ConstructParse)] 2007/12/4, Stefan O'Rear [EMAIL PROTECTED]: On Tue, Dec 04, 2007 at 03:36:20PM +0100, Steffen Mazanek wrote: Hello, I want to quickcheck a property on a datatype representing programs

Re: [Haskell-cafe] ghc overlapping instances - solved

2007-12-06 Thread Steffen Mazanek
Hello, Isaac, this works for me. Thx a lot, Steffen 2007/12/5, Isaac Dupree [EMAIL PROTECTED]: Steffen Mazanek wrote: Hi, Stefan and Isaac, thx for providing quick advice. @Stefan: Unfortunately I have to use a list. @Isaac: I do not get it. Could you please provide a short

Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-08 Thread Steffen Schuldenzucker
(Wrap f) * (Wrap x) = Wrap $ f x convBinOp :: (a - a - a) - (Wrapped a - Wrapped a - Wrapped a) convBinOp op x y = pure op * x * y Best regards, Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

Re: [Haskell-cafe] Ada-style ranges

2010-04-26 Thread Steffen Schuldenzucker
mkBounded :: (Bounded a, Ord a) = (b - a) - b - Maybe a mkBounded f x = case f x of y | minBound = y y = maxBound - Just y | otherwise - Nothing mkRange1 :: Integer - Maybe Range1 mkRange1 = mkBounded Range1 -- Steffen

Re: [Haskell-cafe] Data creation pattern?

2010-05-13 Thread Steffen Schuldenzucker
Hi. Stephen Tetley wrote: Hi Eugene Is something like this close to what you want: For example this builds an object with ordered strings... makeOrdered :: String - String - String - Object makeOrdered a b c = let (s,t,u) = sort3 (a,b,c) in Object s t u Or just: makeOrdered a b c = let

[Haskell-cafe] How to build an Indicator Type for a type class?

2010-06-01 Thread Steffen Schuldenzucker
(instances for Elem so that Elem x l iff x is an element of the list l) Now I want: type family Insert x s :: * Insert x s = s forall (x, s) with (Elem x s) Insert x s = Cons x s for all other (x, s). Thanks a lot! Steffen [1] http://hpaste.org/fastcgi/hpaste.fcgi/view?id=25832

Re: [Haskell-cafe] How to build an Indicator Type for a type class?

2010-06-03 Thread Steffen Schuldenzucker
the HList paper now... Best regards, Steffen http://okmij.org/ftp/Haskell/types.html#class-based-dispatch -Brent On Mon, May 31, 2010 at 01:32:18PM +0200, Steffen Schuldenzucker wrote: Dear Cafe, let: data True data False class C a (arbitrary instances for C may follow) Now, how

Re: [Haskell-cafe] More experiments with ATs

2010-07-04 Thread Steffen Schuldenzucker
to be in scope, and 'a' isn't. There's a GHC ticket for this: http://hackage.haskell.org/trac/ghc/ticket/3714 This works (on my ghc-6.12.2): class Rfunctor f where type F f :: * - * (%) :: f a b - (a - b) - F f a - F f b [...] -- Steffen

[Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-05 Thread Steffen Schuldenzucker
found a way which does not radically alter f's structure). So, does someone know how to solve this or can prove that it can't be solved? Best regards, Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

Fwd: Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-06 Thread Steffen Schuldenzucker
: Tue, 6 Jul 2010 13:25:57 +1200 From: Richard O'Keefe o...@cs.otago.ac.nz To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de On Jul 6, 2010, at 12:23 AM, Steffen Schuldenzucker wrote: Given the definition of a recursive function f in, say, haskell, determine if f can be implemented

Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-06 Thread Steffen Schuldenzucker
On 7/5/2010 8:33 PM, Andrew Coppin wrote: Tillmann Rendel wrote: Hi Steffen, Steffen Schuldenzucker wrote: Given the definition of a recursive function f in, say, haskell, determine if f can be implemented in O(1) memory. Constant functions are implementable in O(1) memory, but interpreters

Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-07 Thread Steffen Schuldenzucker
your data structures to numbers? In that case, only numbers of limited size, the answer is, of course, yes. You can implement any such function in constant space and time. Just make a lookup table. Sent from my iPad On Jul 6, 2010, at 6:37, Steffen Schuldenzucker sschuldenzuc...@uni

Re: [Haskell-cafe] in-equality type constraint?

2010-07-16 Thread Steffen Schuldenzucker
[c] *except* for -- a ~ c. instance (TypeEq a c x, x ~ HFalse) = a b [c] where -- ... Best regards, Steffen [1] http://hackage.haskell.org/packages/archive/HList/0.2.3/doc/html/Data-HList-FakePrelude.html#t%3ATypeEq (Note that for it to work over all types, you have to import one

Re: [Haskell-cafe] in-equality type constraint?

2010-07-17 Thread Steffen Schuldenzucker
On 07/17/2010 03:50 AM, Gábor Lehel wrote: Does TypeEq a c HFalse imply proof of inequality, or unprovability of equality? Shouldn't these two be equivalent for types? On Sat, Jul 17, 2010 at 2:32 AM, Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de wrote: On 07/17/2010 01:08 AM, Paul L

Re: [Haskell-cafe] Ghci :ctags or hasktags print to standard out instead of file

2009-10-10 Thread Steffen Schuldenzucker
:ctags foo | ghci your_file.hs /dev/null Not the nice way, of course. Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] What does the `forall` mean ?

2009-11-12 Thread Steffen Schuldenzucker
Andrew Coppin wrote: I just meant it's not immediately clear how foo :: forall x. (x - x - y) is different from foo :: (forall x. x - x) - y Uhm, I guess you meant foo :: forall x. ((x - x) - y) VS. foo :: (forall x. x - x) - y , didn't you?

Re: [Haskell-cafe] Partially applied functions

2009-11-28 Thread Steffen Schuldenzucker
on the function how much information about the parameters can be read from the result. -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] lawless instances of Functor

2010-01-04 Thread Steffen Schuldenzucker
$ x * 9 + 4 fmap (+1) . fmap (*3) $ (Foo x) == Foo $ x * 3 * 3 + 1 + 1 == Foo $ x * 9 + 2 -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] lawless instances of Functor

2010-01-05 Thread Steffen Schuldenzucker
Brent Yorgey wrote: On Mon, Jan 04, 2010 at 11:49:33PM +0100, Steffen Schuldenzucker wrote: [...] As others have pointed out, this doesn't typecheck; but what it DOES show is that if we had a type class class Endofunctor a where efmap :: (a - a) - f a - f a then it would

Re: [Haskell-cafe] classes with types which are wrapped in

2010-01-22 Thread Steffen Schuldenzucker
, but has been given 0 In the instance declaration for `X A_2 Int' However, this error message looks strange. I tried to reduce this to a simpler case[1] and got the same message. Does anyone know why it complains just about the number of type arguments (which is correct) ? -- Steffen [1

Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Steffen Schuldenzucker
I don't know too much about GADTs, but it works fine with fundeps: http://hpaste.org/40535/finite_list_with_fundeps (This is rather a draft. If anyone can help me out with the TODOs, I'd be happy.) -- Steffen On 10/13/2010 10:40 AM, Eugene Kirpichov wrote: Well, in my implementation it's

Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Steffen Schuldenzucker
Hmm, ok, I simplified the idea[1] and it looks like I'm getting the same problem as you when trying to drop the 'n' parameter carrying the length of the list. Sad thing. [1] http://hpaste.org/40538/finite_list__not_as_easy_as_i On 10/13/2010 10:43 AM, Steffen Schuldenzucker wrote: I don't

Re: [Haskell-cafe] Am I using type families well?

2010-11-01 Thread Steffen Schuldenzucker
was automatic in Haskell, well I was wrong... Thanks ! Just out of curiosity: Does it work if you omit eval's type signature? -- Steffen 2010/11/1 Sjoerd Visscher sjo...@w3future.com mailto:sjo...@w3future.com Hi, There's nothing wrong with your type families. The problem

Re: [Haskell-cafe] What is simplest extension language to implement?

2010-11-02 Thread Steffen Schuldenzucker
On 11/02/2010 10:40 AM, Yves Parès wrote: Because he would have either to recompile the whole program or to use things like hint, both implying that GHC must be installed on the user side (600Mo+ for GHC 6.12.3) Isn't there a way to use some stripped-down version of ghc and the base libraries,

Re: [Haskell-cafe] Problem on overlapping instances

2011-01-05 Thread Steffen Schuldenzucker
Am 05.01.2011 09:24, schrieb Magicloud Magiclouds: Hi, I am using Data.Binary which defined instance Binary a = Binary [a]. Now I need to define instance Binary [String] to make something special for string list. How to make it work? I looked into the chapter of overlappinginstances,

Re: [Haskell-cafe] Re: Converting IO [XmlTree] to [XmlTree]

2009-04-28 Thread Steffen Schuldenzucker
: every monad is an applicative; every applicative is a functor; every functor is pointed. Uhm, isn't it: class (Functor f) = Pointed f where pure :: a - f a -- singleton, return, unit etc. Got it from: The Typeclassopedia by Brent Yorgey (forgot the URL, sorry) Steffen

Re: [Haskell-cafe] Re: Converting IO [XmlTree] to [XmlTree]

2009-04-28 Thread Steffen Schuldenzucker
() against shape = [()] against shape = [] Steffen [1] http://thread.gmane.org/gmane.comp.lang.haskell.cafe/54685 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Haskell Arrows Applications

2009-05-06 Thread Steffen Schuldenzucker
combinators allow them to be used together in a clean way. There are Arrows that carry mutable state and perform IO, too. Also see the wiki page [2] and Hackage documentation [3]. It took me a while to understand what really goes on, but worked quite well then. Steffen [1] http://hackage.haskell.org

Re: [Haskell-cafe] Trying to Express Constraints using a data structure

2009-05-18 Thread Steffen Schuldenzucker
and they solved it using a data structure: http://www.cse.unsw.edu.au/~chak/papers/LCGK09.html Hope that helps. Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] SLD resolution code in Haskell

2009-08-28 Thread Steffen Bock
Hi, is there any haskell code for SLD-resolution; I wanna learn it. Thanks a lot. Steffen. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Problem with Infinite Lists

2003-09-03 Thread Steffen Mazanek
Hello, all_fib :: [Float] You define all_fib to return a list of Float, but even does only work for numbers whose type is an instance of the class Integral, e.g. Int. HTH and ciao, Steffen ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http

[Haskell-cafe] Re: [Haskell] Haskell Chess

2007-03-19 Thread Steffen Mazanek
description used in the exercises; the English version will be the wiki (although it has no convert2tex function). Best regards, Steffen Donald Bruce Stewart schrieb: smazanek: Hello again, I got a lot of interesting and useful comments on my posting about Haskell Chess. Somebody

Re: [Haskell-cafe] Haskell Chess

2007-03-19 Thread Steffen Mazanek
, interesting other games are probably too diverse to be pressed in a general framework, aren't they? Henning Thielemann schrieb: On Mon, 19 Mar 2007, Andrew Wagner wrote: Steffen, I've done some chess AI programming in the past, so I'd be happy to help with this project. I have some pretty

[Haskell-cafe] generate Haskell code from model

2007-04-13 Thread Steffen Mazanek
are well known. Best practices in programming are propagated, for Haskell e.g. use different modules for different things, use the tedious import/export lists, Haddock your code... What are your ideas? Best regards, Steffen -- Dipl.-Inform. Steffen Mazanek Institut für Softwaretechnologie

Re: [Haskell-cafe] generate Haskell code from model

2007-04-13 Thread Steffen Mazanek
have no choice and are not allowed to discuss the sense of this approach :-) How should the code look like? Best regards, Steffen 2007/4/13, Brian Smith [EMAIL PROTECTED]: On 4/13/07, Steffen Mazanek [EMAIL PROTECTED] wrote: Hello everybody, I would like to start a discussion on how

Re: [Haskell-cafe] generate Haskell code from model

2007-04-13 Thread Steffen Mazanek
structures that operate on this data. How would you procede? This is similar to HaXML that helped you to generate Haskell types for an xml schema. Best regards, Steffen -- Dipl.-Inform. Steffen Mazanek Institut für Softwaretechnologie Fakultät Informatik Universität der Bundeswehr München 85577

Re: [Haskell-cafe] Tutorial on Haskell

2007-04-16 Thread Steffen Mazanek
___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Dipl.-Inform. Steffen Mazanek Institut für Softwaretechnologie Fakultät Informatik Universität der Bundeswehr München 85577 Neubiberg Tel: +49 (0)89 6004-2505 Fax: +49 (0)89 6004-4447 E

Re: [Haskell-cafe] generate Haskell code from model

2007-05-09 Thread Steffen Mazanek
-mazanek.de/blog/2007/05/visual-language-howto.html Best regards, Steffen 2007/4/14, Brian Smith [EMAIL PROTECTED]: On 4/14/07, Steffen Mazanek [EMAIL PROTECTED] wrote: Brian, but don't you think that you have to write a lot of boilerplate code in Haskell? I have never felt I was writing

Re: [Haskell-cafe] generate Haskell code from model

2007-05-10 Thread Steffen Mazanek
it will be no problem to define a DSL for itself :-) Ciao, Steffen If thats the case, how is Translate to Haskell different from Translate to C++? It only makes a difference if you go in and edit the result, but then you've lost your model? The other thing is that defining a domain specific language is well

[Haskell-cafe] Profiling, measuring time

2007-05-19 Thread Steffen Mazanek
, Steffen -- Dipl.-Inform. Steffen Mazanek Institut für Softwaretechnologie Fakultät Informatik Universität der Bundeswehr München 85577 Neubiberg Tel: +49 (0)89 6004-2505 Fax: +49 (0)89 6004-4447 E-Mail: [EMAIL PROTECTED] ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Profiling, measuring time

2007-05-20 Thread Steffen Mazanek
Thats it! Thanks a lot. I do not even need forceOutput, because I perform a bottom-up analysis. And the timeline I got looks sooo great (perfect polynomial behavior :-)) Best regards, Steffen 2007/5/20, Matthew Brecknell [EMAIL PROTECTED]: Steffen Mazanek: I have written a function f

[Haskell-cafe] List algorithm

2007-05-21 Thread Steffen Mazanek
]) would do the job, however I am looking for a more efficient approach. Help is greatly appreciated, even a google search term would be fine :-) I really hope for a polynomial algorithm although I am not very optimistic about this. Ciao, Steffen ___ Haskell

Re: [Haskell-cafe] List algorithm

2007-05-22 Thread Steffen Mazanek
of length i I wanted to iterate over all productions p, counting the number n of Nonterminals at the right-hand side of p, computing all lists with n numbers whose sum is i and split the span accordingly. It works, however, the strings have to be very, very short *g* Ciao and Thx, Steffen 2007/5/22

[Haskell-cafe] CYK-style parsing and laziness

2007-05-23 Thread Steffen Mazanek
. Is there a trick to get lazy evaluation into play here? It is sufficient to find only one occurence of the start symbol in gs n 1. Best regards, Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell-cafe] Re: CYK-style parsing and laziness

2007-05-23 Thread Steffen Mazanek
comprehension however this is evaluated too late. I should really use sets, however, I would miss the list comprehension syntactic sugar sooo much. Is there something similar for real Data.Set? Best regards, Steffen ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] Re: CYK-style parsing and laziness

2007-05-26 Thread Steffen Mazanek
implementation. This is really enlightening. Ciao, Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] standard function

2007-06-06 Thread Steffen Mazanek
Hello, is there a function f::[a-b]-a-[b] in the libraries? Couldn't find one using hoogle although this seems to be quite a common thing... Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

Re: [Haskell-cafe] Re: standard function

2007-06-06 Thread Steffen Mazanek
Cool! Haskell surprised me once again :) @Paul: Thank you for pointing me to the old thread. @Neil: Is there a way to let hoogle find this kind of stuff? It would be a quite complex inference though. 2007/6/6, apfelmus [EMAIL PROTECTED]: Steffen Mazanek wrote: is there a function f::[a-b

[Haskell-cafe] HXT: desperatedly trying to concat

2009-04-02 Thread Steffen Schuldenzucker
or multiple results (what I don't want either). I'd be really happy if someone could save my day and help me with this issue. Thanks in advance, Steffen Neu bei WEB.DE: Kostenlose maxdome Movie-FLAT! https://register.maxdome.de/xml

[Haskell-cafe] Re: HXT: desperatedly trying to concat

2009-04-02 Thread Steffen Schuldenzucker
gonna make a big WATCH YOUR PARENTHESES! poster... Yeah, with some arrows on it... Thanks for reading, anyway. Steffen Neu bei WEB.DE: Kostenlose maxdome Movie-FLAT! https://register.maxdome.de/xml/order/LpWebDe?ac

[Haskell-cafe] Tool for evaluating GHCi lines in a source file

2011-01-23 Thread Steffen Schuldenzucker
Hi, some time ago I read of a small tool that extracts lines like GHCi some_expression from a source file and appends GHCi's output to them. Now I can't find it again. Does anyone remember its name? Thanks. Steffen ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Tool for evaluating GHCi lines in a source file

2011-01-23 Thread Steffen Schuldenzucker
On 01/23/2011 06:48 PM, Max Rabkin wrote: On Sun, Jan 23, 2011 at 12:35, Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de wrote: Hi, some time ago I read of a small tool that extracts lines like GHCi some_expression from a source file and appends GHCi's output to them. Now I can't find

Re: [Haskell-cafe] combined parsing pretty-printing

2011-01-26 Thread Steffen Schuldenzucker
. Is there any work to combine the two? You might want to take a look at [1, 2]XML Picklers from [3]HXT. Steffen [1] http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML [2] http://blog.typlab.com/2009/11/writing-a-generic-xml-pickler/ [3] http://hackage.haskell.org/package

Re: [Haskell-cafe] Instantiation problem

2011-01-29 Thread Steffen Schuldenzucker
= const Centimetre as in the instance for Metre Steffen On 01/28/2011 12:42 PM, Patrick Browne wrote: Below is some code that is produces information about the *types* used for measuring (e.g. metres). The following evaluation returns 1.00 which the convert factor for metres

Re: [Haskell-cafe] Typing problem

2011-01-31 Thread Steffen Schuldenzucker
) = [t] - (t, t1) -- Steffen On 01/31/2011 06:29 PM, michael rice wrote: I'm mapping a function over a list of data, where the mapping function is determined from the data. g f l = map (g l) l So g serialize prolog - [4,5,3,2,3,1] But I'm having typing problems trying to do a similar thing

Re: [Haskell-cafe] Inheritance and Wrappers

2011-01-31 Thread Steffen Schuldenzucker
such as {-# LANGUAGE GeneralizedNewtypeDeriving #-} data Wrapper a = Wrap a deriving (Eq, Ord, Read, Show, Num) -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] ($) not as transparent as it seems

2011-02-03 Thread Steffen Schuldenzucker
Dear cafe, does anyone have an explanation for this?: error (error foo) *** Exception: foo error $ error foo *** Exception: *** Exception: foo -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

Re: [Haskell-cafe] ($) not as transparent as it seems

2011-02-03 Thread Steffen Schuldenzucker
Thanks to all of you for making GHC's behaviour yet a bit clearer to me. On 02/03/2011 11:25 PM, Daniel Fischer wrote: On Thursday 03 February 2011 23:03:36, Luke Palmer wrote: This is probably a result of strictness analysis. error is technically strict, so it is reasonable to optimize

Re: [Haskell-cafe] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker
sendSomeAnswer conn $ processSomeData someData ... -- Steffen Regards, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe

Re: [Haskell-cafe] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker
$ prep ++ request runServer r And then: *MyModule r - startMyServer (plain echo server running) *MyModule someFunction hello r (now echo server with prepend hello) *MyModule someFunction world r (now echo server with prepend helloworld) -- Steffen On 02/04/2011 03:41 PM, C K Kashyap wrote

Re: [Haskell-cafe] Extending GHCi

2011-02-07 Thread Steffen Schuldenzucker
On 02/07/2011 12:45 PM, C K Kashyap wrote: $ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package

Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Steffen Schuldenzucker
: add a type signature that fixes these type variable(s) And then, specializing evil's type: let good = appendLog Foo Bar :: Sealed Admin String unseal (undefined :: Admin) good FooBar -- Steffen On 02/09/2011 06:15 PM, Cristiano Paris wrote: Hi all, I've a type problem that I cannot solve

Re: [Haskell-cafe] Proving correctness

2011-02-11 Thread Steffen Schuldenzucker
On 02/11/2011 12:06 PM, C K Kashyap wrote: [...] I know that static typing and strong typing of Haskell eliminate a whole class of problems - is that related to the proving correctness? [...] You might have read about free theorems arising from types. They are a method to derive certain

Re: [Haskell-cafe] Having trouble with instance context

2011-02-23 Thread Steffen Schuldenzucker
] in this direction can however be taken with the current state of the language. -- Steffen [1] http://haskell.org/haskellwiki/GHC/AdvancedOverlap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] object oriented technique

2011-03-29 Thread Steffen Schuldenzucker
- Double - Shape rectangle x y w h = ... (analogous) shapes = [rectangle 1 2 3 4, circle 4 3 2, circle 1 1 1] -- Steffen On 03/29/2011 07:49 AM, Tad Doxsee wrote: I've been trying to learn Haskell for a while now, and recently wanted to do something that's very common in the object oriented

Re: [Haskell-cafe] Generating random graph

2011-04-10 Thread Steffen Schuldenzucker
forM [1..graphSize] loop. Try: weights - replicateM (length others) $ randomRIO (1, 10) instead. -- Steffen But I noticed that graph has sometimes same weights on different edges. This is very unlikely to happen so probably I have some error using random generators. Could somebody tell me

Re: [Haskell-cafe] A small Darcs anomoly

2011-04-28 Thread Steffen Schuldenzucker
On 04/28/2011 05:23 PM, malcolm.wallace wrote: Unfortunately, sharing a build directory between separate repositories does not work. After a build from one repository, all the outputs from that build will have modification times more recent than all the files in the other repository. Then I

Re: [Haskell-cafe] Server hosting

2011-05-06 Thread Steffen Schuldenzucker
On 05/06/2011 08:07 PM, Andrew Coppin wrote: [...] I currently have a website, but it supports only CGI *scripts* (i.e., Perl or PHP). It does not support arbitrary CGI *binaries*, which is what I'd want for Haskell. In fact, I don't have control over the web server at all; I just put content on

Re: [Haskell-cafe] Comment Syntax

2011-06-03 Thread Steffen Schuldenzucker
Am 03.06.2011 10:32, schrieb Guy: What might --| mean, if not a comment? It doesn't seem possible to define it as an operator. Obviously, anyone who is going to write a formal logic framework would want to define the following operators ;) : T |- phi: T proves phi T |-- phi: T proves phi

Re: [Haskell-cafe] Are casts required?

2011-06-06 Thread Steffen Schuldenzucker
= 3 :: (Integral x = x) *Main :t i3 i3 :: Integer and the same thing happens on the (newId startId) side, too. As one last remark, your original problem that caused the Ambiguous type variable error looks very similar to the well-known (show . read) problem. -- Steffen

Re: [Haskell-cafe] Hackage Server not reachable

2011-06-22 Thread Steffen Schuldenzucker
://hackage.haskell.org is 69.30.63.204 Same result for me. I also cannot access any of the Hackage web pages. No problem here. What is the error for you? hackage.haskell.org doesn't seem to answer pings btw. -- Steffen ___ Haskell-Cafe mailing

[Haskell-cafe] Fwd: Re: Hackage Server not reachable

2011-06-22 Thread Steffen Schuldenzucker
Forwarding to -cafe. Original Message Subject:Re: [Haskell-cafe] Hackage Server not reachable Date: Wed, 22 Jun 2011 20:43:59 +1000 From: Stuart Coyle stuart.co...@gmail.com To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de Cabal fails with a timeout

Re: [Haskell-cafe] Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker
a) = Bool - [a] - [a] - Bool generates precisely xs g = if null g then null xs else (not precisely || length xs `mod` length g == 0) xs `isPrefixOf` cycle g -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

  1   2   >