Re: [Haskell-cafe] Fwd: [Haskell-beginners] Monad instances and type synonyms

2013-04-14 Thread Steffen Schuldenzucker
The point in not allowing partially applied type synonym instances is that it'd make deciding whether a type is an instance of a class much harder. Cf. here[1] for a similar question with the Category class. -- Steffen [1] Attached message. Couldn't find it on the archives.. On

Re: [Haskell-cafe] code-as-config, run-time checks and error locations

2013-04-07 Thread Steffen Schuldenzucker
This one[1] sounds so awesome! I just read the paper. In particular I like how one could access the current call stack structure live. However, the most recent changes to the code are from early 2009. Anyone knows what happened to this? [1] http://hackage.haskell.org/trac/ghc/wiki/ExplicitCa

Re: [Haskell-cafe] code-as-config, run-time checks and error locations

2013-04-06 Thread Steffen Schuldenzucker
Sun, Apr 7, 2013 at 12:23 AM, Steffen Schuldenzucker wrote: For the moment I think it would be enough to auto-insert the location of calls to a certain set of functions. Have you tried assert [1]? [1] http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Control-Exception.html#v:asse

[Haskell-cafe] code-as-config, run-time checks and error locations

2013-04-06 Thread Steffen Schuldenzucker
ES defined at analysis1.hs:13:8 I'm not yet sure which level of granularity I want for error messages and one can probably get arbitrarily fancy on this. For the moment I think it would be enough to auto-insert the location of calls to a certain set of functions. Any

Re: [Haskell-cafe] monoid pair of monoids?

2012-12-21 Thread Steffen Schuldenzucker
= Nil mappend Nil Nil = Nil instance (Monoid a, Monoid bs) => Monoid (Cons a bs) where mempty = Cons mempty mempty mappend (Cons x1 ys1) (Cons x2 ys2) = Cons (mappend x1 x2) (mappend ys1 ys2) -- Steffen ___ Haskell-Cafe mailing list Haske

[Haskell-cafe] ANNOUNCE: apphointments - A simple functional calendar

2012-10-18 Thread Steffen Schuldenzucker
Using just haskell instead of our own language or GUI allows great flexibility in both defining events and generating reports. See e.g. the 'lecture' combinator from Apphointments.Util. Status -- Works for me, but has no features yet. See TODO. Credi

Re: [Haskell-cafe] How to define a Monad instance

2012-07-28 Thread Steffen Schuldenzucker
; :> 'B' But I can't figure a way to define a Monad instance for that. :( The desugaring of the example looks like this: ('a' :> 'b') >> ('A' :> 'B') Only (>>) is used, but not (>>=) (i.e. results are always discarded). If this is the only case that makes sense, you're probably looking for a Monoid instead (see above) -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Finding the average in constant space

2012-05-27 Thread Steffen Schuldenzucker
y. - Looks pretty much like your 'Fold' type with an additional state (done or not yet done). Also, the pipe package seems to provide something similar. -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] [Haskell] ANNOUNCE: notcpp-0.0.1

2012-04-15 Thread Steffen Schuldenzucker
resolution has its drawbacks :/"[1] a compile time error. -- Steffen [1] http://hackage.haskell.org/packages/archive/notcpp/0.0.1/doc/html/NotCPP-ScopeLookup.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Understanding GC time

2012-03-12 Thread Steffen Schuldenzucker
st into memory (at least not accidentally). You might want to take a look at iteratees or conduits. -- Steffen 2012/3/10 Anthony Cowley: From that profiling data, I think you're just seeing a decrease in sharing. With one thread, you create the list structure in memory: the first f

Re: [Haskell-cafe] STM atomic blocks in IO functions

2012-01-14 Thread Steffen Schuldenzucker
after 'atomically' won't be influenced by any other threads while it's running, hence the name. -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] named pipe interface

2012-01-12 Thread Steffen Schuldenzucker
hGetLine fromA axiom :: String -> String -> String axiom str = showString (unsafePerformIO $ axiomIO str) -- Examples of usage tl;dr, but did you try to write your program without using unsafePerformIO? It&#x

Re: [Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-06 Thread Steffen Schuldenzucker
On 01/06/2012 11:51 AM, Steve Horne wrote: On 06/01/2012 10:29, Steffen Schuldenzucker wrote: On 01/06/2012 11:16 AM, Steve Horne wrote: >>> [...] module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where -- n : node type -- d : data item type wrapped in each node class Walkab

Re: [Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-06 Thread Steffen Schuldenzucker
ependent. Did you try something like > {-# LANGUAGE MultiParamTypeClasses #-} > class WalkableBinTree n d where > ... (same code as above, but 'd' is bound now) > ... > instance WalkableBinTree (BT x) x where > ... -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Anonymous, Unique Types, maybe

2011-12-04 Thread Steffen Schuldenzucker
or times in the type system. I just wanted the compiler to check if it could prove two prices are compatible and if not, I would convert them (which was cheap). Using more sophisticated types for 'n', we can express richer properties. For example: > data S n > > my

Re: [Haskell-cafe] Anonymous, Unique Types, maybe

2011-12-04 Thread Steffen Schuldenzucker
de note, with the 'type' keyword, AList, BList, CList will /not/ be seen as separate types (but they're all the same type, namely [Event]). If you want separate types, you would use a newtype wrapper like newtype AList = AList [Event] deriving (some instances you wa

Re: [Haskell-cafe] Fwd: Is it possible to represent such polymorphism?

2011-10-06 Thread Steffen Schuldenzucker
On 10/05/2011 11:30 PM, Alberto G. Corona wrote: if Hlist is sugarized as variable length tuples, then the initial code would compile without noticing the use of HList... Seems to me like the advantage of such a sugaring would be that people could use a complex framework without actually havi

Re: [Haskell-cafe] Problem on using class as type.

2011-10-03 Thread Steffen Schuldenzucker
On 10/03/2011 10:42 PM, Magicloud Magiclouds wrote: Hi, I have a function: post :: (ToJson p, FromJson q) => String -> String -> String -> Map.Map String p -> IO q Now I'd like to call it like: r<- post site token "user.addMedia" (Map.fromList [ ("users", users :: ToJson)

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

2011-09-08 Thread steffen
bitbucket plus 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 pro

[Haskell-cafe] Fwd: Re: How to select last inserted record from Table Using Database.HSQL.MySQL

2011-07-26 Thread Steffen Schuldenzucker
Forwarding to list Original Message Subject:Re: [Haskell-cafe] How to select last inserted record from Table Using Database.HSQL.MySQL Date: Tue, 26 Jul 2011 14:27:56 +0300 From: Sergiy Nazarenko To: Steffen Schuldenzucker Thanx a lot! I could solve that

Re: [Haskell-cafe] How to select last inserted record from Table Using Database.HSQL.MySQL

2011-07-25 Thread Steffen Schuldenzucker
c/refman/5.0/en/information-functions.html#function_last-insert-id There probably exist similar functions for other sql databases. -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Make Show instance

2011-07-21 Thread Steffen Schuldenzucker
Tree k v) where show EmptyTree = show "Empty" show (Node (Int, Int) left right) = .. I'm afraid to say that, but 'Int' doesn't make sense at this place. You would want > show (Node (x, y) left right) = ... instead. (That is, use any va

Re: [Haskell-cafe] pointer equality

2011-07-21 Thread Steffen Schuldenzucker
On 07/21/2011 02:15 PM, Alexey Khudyakov wrote: Any examples for hangups of 'smartEq' are greatly appreciated, I couldn't produce any so far. Following sequences will hang smartEq. They are both infinite and aperiodic. smartEq (fromList primes) (fromList primes) smartEq (fromList pidigits)

Re: [Haskell-cafe] pointer equality

2011-07-21 Thread Steffen Schuldenzucker
eqPairs) Examples: *Main> smartEq (Cycle $ fromList [1]) (Cycle $ fromList [1,1]) True *Main> smartEq (Cons 1 $ Cycle $ fromList [1]) (Cycle $ fromList [1]) True *Main> smartEq (Cons 2 $ Cycle $ fromList [1]) (Cycle $ fromList [1]) False Any examples for hangups of 'smartEq&#

Re: [Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Steffen Schuldenzucker
for any v :: V, and match the second case. But as 'Varref' does not add an AssignCap constraint, 'test' must not either. Hope that helps. Steffen Thanks, -Ryan {-# LANGUAGE GADTs #-} class AssignCap m data PureT data IOT instance AssignCap IOT data E m where

Re: [Haskell-cafe] class and instance

2011-07-10 Thread Steffen Schuldenzucker
is arbitrary, your definition of the class 'Points' could be simplified to > class Points p where > -- "forall a" is added implicitly. > getX :: p a -> a > getY :: p a -> a > instance Points Point where > -- copy'n'paste from above -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Arrow instance of function type [a] -> [b]

2011-07-06 Thread Steffen Schuldenzucker
osed to be, Prelude.id (as given by the general instance for functions) or map Prelude.id (given by your instance)? -- Steffen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Automatic Reference Counting

2011-07-05 Thread steffen
you don't implement 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

Re: [Haskell-cafe] overloading show function

2011-06-29 Thread Steffen Schuldenzucker
it might lead to unexpected results. For a similar problem, you may want to consult the haskell wiki[1]. -- 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] Fwd: Re: Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker
Michael, On 06/27/2011 01:51 PM, Steffen Schuldenzucker wrote: > > Forwarding to -cafe > > Original Message > Subject: Re: [Haskell-cafe] Period of a sequence > Date: Mon, 27 Jun 2011 04:46:10 -0700 (PDT) > From: michael rice > To: Steffen Schuld

[Haskell-cafe] Fwd: Re: Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker
Forwarding to -cafe Original Message Subject:Re: [Haskell-cafe] Period of a sequence Date: Mon, 27 Jun 2011 04:46:10 -0700 (PDT) From: michael rice To: Steffen Schuldenzucker Hi Steffen, Repeating decimals. 5/7 == 0.714285 714285 7142857 ... Period = 6

Re: [Haskell-cafe] Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker
[1,2,3,1,2,1,2] [1,2,3,1,2] > -- False > -- > -- >>> generates False [1,2,3,1,2,1,2] [1,2,3,1,2] > -- True > generates :: (Eq a) => Bool -> [a] -> [a] -> Bool > generates precisely xs g = if null g > then null xs > else (not precisely || length xs

[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 To: Steffen Schuldenzucker Cabal fails with a timeout like this: stuart@Panforte:~/Code/gift-parser

Re: [Haskell-cafe] Hackage Server not reachable

2011-06-22 Thread Steffen Schuldenzucker
l.org <http://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 __

Re: [Haskell-cafe] Are casts required?

2011-06-06 Thread Steffen Schuldenzucker
h is probably caused by defaulting on the top level (IIRC, an unresolved Integral type variable defaults to Integer. Don't have the documentation at hand right now.) like this: *Main> let i3 = 3 :: (Integral x => x) *Main> :t i3 i3 :: Integer and the same thing happens on the (

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 dir

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] 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 sug

Re: [Haskell-cafe] Generating random graph

2011-04-10 Thread Steffen Schuldenzucker
ated, but it is used again in the next iteration of the toplevel 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

Re: [Haskell-cafe] object oriented technique

2011-03-29 Thread Steffen Schuldenzucker
w y ++ ") -- "" ++ show r rectangle :: Double -> Double -> Double -> 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

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 dele

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

2011-03-11 Thread steffen
.framework/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.

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 http://www.haskell.org/m

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

2011-03-10 Thread steffen
ou've install Xcode 4. Maybe a symbolic link "ln -s crt1.10.6.o crt1.10.5.o" in /usr/lib shall do 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] Having trouble with instance context

2011-02-23 Thread Steffen Schuldenzucker
esn't have a way to express this (yet?). Some steps[1] 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] 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 prop

Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Steffen Schuldenzucker
t :1:11-31 Probable fix: 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

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 ff

Re: [Haskell-cafe] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker
AcceptConnection > request <- getSomeData client > prep <- readIORef r > sendSomeAnswer client $ prep ++ request > runServer r And then: *MyModule> r <- startMyServer (plain echo server running) *MyModule> someFunction "hello" r (now echo server

Re: [Haskell-cafe] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker
ata <- getSomeData conn *MyModule> sendSomeAnswer conn $ processSomeData someData ... -- Steffen Regards, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/

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 t

[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-C

Re: [Haskell-cafe] Inheritance and Wrappers

2011-01-31 Thread Steffen Schuldenzucker
n make your wrapper code less clumsy by deriving some instances 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

Re: [Haskell-cafe] Typing problem

2011-01-31 Thread Steffen Schuldenzucker
type for 'sumlen'. Without the type signature, it is inferred to sumlen :: (Num t, Num t1) => [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 =

Re: [Haskell-cafe] Instantiation problem

2011-01-29 Thread Steffen Schuldenzucker
i.e. unit = 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

Re: [Haskell-cafe] tricky recursive type instance method

2011-01-27 Thread Steffen Schuldenzucker
w, Num, Real) > >instance Real a => DAlgebra (FromReal a) (FromReal a) where > conj= id > abs2 x = x*x Steffen [1] http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap On 01/28/2011 04:35 AM, Frank Kuehnel wrote: Hi folks, how do I make this work: I want a division algebra

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

2011-01-26 Thread Steffen Schuldenzucker
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] 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 wrote: > On 25 January 2011 02:12, Ivan Lazar Miljenovic > wrote: > > > > > > > > > > > On 25 January 2011 12:05, Aaron Gray wrote: > > > On 24 January 2011 23:01, Iva

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 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 fin

[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 ___ Ha

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] 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-in

Re: [Haskell-cafe] Manatee Video.

2010-11-30 Thread steffen
combining 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 wrote: > steffen writes: > > Hi Andy, > > > Can you please do something abo

[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 wrote: > Hi all, > > Many people as

[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 Transforme

Re: Fwd: [Haskell-cafe] DSL libraries

2010-11-07 Thread steffen
tps://gist.github.com/666121 On 4 Nov., 18:51, Dupont Corentin wrote: > Nobody had the compilation messages I had? > > > > > > > > -- Forwarded message -- > From: Dupont Corentin > Date: Tue, Nov 2, 2010 at 2:30 PM > Subject: [Haskell-cafe] DSL libra

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] Am I using type families well?

2010-11-01 Thread Steffen Schuldenzucker
> I thought that this kind of matching 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 mailto:sjo...@w3future.com>> > > Hi, > >

[Haskell-cafe] Re: State & nested structures

2010-10-29 Thread steffen
t; > On Fri, Oct 29, 2010 at 6:19 PM, steffen > wrote: > > > > > > > > > > > > Horribly enough this one seems to work... > > > > mapOnBofA :: SB a -> SA a > > > mapOnBofA mf = get >>= \st@(A {b=temp}) -> > > >      

[Haskell-cafe] Re: State & nested structures

2010-10-29 Thread steffen
in > > On Fri, Oct 29, 2010 at 6:19 PM, steffen > wrote: > > > > > > > > > > > > Horribly enough this one seems to work... > > > > mapOnBofA :: SB a -> SA a > > > mapOnBofA mf = get >>= \st@(A {b=temp}) -> > > >

[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 comp

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

2010-10-28 Thread steffen
nly define the Foldr constructor 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

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

2010-10-26 Thread steffen
return.Left) (sequence >=> return . sequence) On 27 Okt., 06:12, steffen 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 evalO

[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: 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 * >

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 wrot

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 implem

[Haskell-cafe] Re: EDSL for Makefile

2010-10-06 Thread steffen
test = sh $ "gcc -o" & target & sources which looks somewhat nicer. This example also defines runTest and a test function (which calls the shell command "echo" to print some lines) you can try in ghci by typing "runTest test"... [1] http://gist.github.com

[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 shor

[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: 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 syst

[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 wrote: > > Thanks Emil ... yeah, that works...I was wondering what I could do to > > not have to menti

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 program

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] > > editRec

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 > wrote: >> On 07/17/2

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

2010-07-16 Thread Steffen Schuldenzucker
rovide an instance C a b [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

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

2010-07-06 Thread Steffen Schuldenzucker
Lennart Augustsson wrote: > Are you limiting 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

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

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

2010-07-06 Thread Steffen Schuldenzucker
Date: Tue, 6 Jul 2010 13:25:57 +1200 From: Richard O'Keefe To: Steffen Schuldenzucker 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 in O(1) memory. How are you s

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

2010-07-05 Thread Steffen Schuldenzucker
ave to be kept in memory during the call to (f (x-2) (y+1)), therefore f cannot be implemented in constant memory. (read: I haven't 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

Re: [Haskell-cafe] More experiments with ATs

2010-07-04 Thread Steffen Schuldenzucker
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 mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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

2010-06-03 Thread Steffen Schuldenzucker
7;m gonna read 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: >> >>&g

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

2010-06-01 Thread Steffen Schuldenzucker
re just (unsorted) lists like this: > data Nil > data Cons a b > class Elem x l (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 (

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 = le

Re: [Haskell-cafe] Ada-style ranges

2010-04-26 Thread Steffen Schuldenzucker
minBound = Range1 $ -5 maxBound = Range1 $ 10 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 -> Nothin

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

2010-03-08 Thread Steffen Schuldenzucker
ap $ f x > > instance Applicative Wrapped where > pure = Wrap > (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 __

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

2010-01-22 Thread Steffen Schuldenzucker
stances) i get: Type synonym `A_2' should have 1 argument, 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

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

Re: [Haskell-cafe] lawless instances of Functor

2010-01-04 Thread Steffen Schuldenzucker
onsider Foo Int and fmap ((+1) . (*3)) (Foo x) == Foo $ (x * 3 + 1) * 3 + 1 == Foo $ 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] Partially applied functions

2009-11-28 Thread Steffen Schuldenzucker
er back out of the partial applied function by passing 0 as a second parameter. It clearly depends 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

  1   2   >