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 04/14/2013

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]

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

2013-04-06 Thread Steffen Schuldenzucker
Dear Café, I'm working on a EDSL that will include both type checks (at compile time) and semantic checks (at run time). - Semantic properties are known at compile time but feel too complex to me to be encoded in the type system. If one of the runtime checks fails, I'd like to print the

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

2013-04-06 Thread Steffen Schuldenzucker
, 2013 at 12:23 AM, Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de 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

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

2012-12-21 Thread Steffen Schuldenzucker
Hi Christopher, On 12/21/2012 09:27 AM, Christopher Howard wrote: [...] Of course, I thought it would be likely I would want other classes and instances with additional numbers of types: code: data Socket3 a b c = Socket3 a b c deriving (Show) instance (Monoid a, Monoid b, Monoid

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

2012-10-18 Thread Steffen Schuldenzucker
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. Credits --- Created by Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de

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

2012-07-28 Thread Steffen Schuldenzucker
On 07/28/2012 03:35 PM, Thiago Negri wrote: [...] As Monads are used for sequencing, first thing I did was to define the following data type: data TableDefinition a = Match a a (TableDefinition a) | Restart So TableDefinition a is like [(a, a)]. [...] So, to create a replacement table:

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

2012-05-27 Thread Steffen Schuldenzucker
Hi Chris, On 05/27/2012 10:04 AM, Chris Wong wrote: I just came up with a way of executing multiple folds in a single pass. In short, we can write code like this: average = foldLeft $ (/)$ sumF* lengthF and it will only traverse the input list once. The code is at:

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

2012-04-15 Thread Steffen Schuldenzucker
On 04/13/2012 10:49 PM, Ben Millwood wrote: I'm pleased to announce my first genuinely original Hackage package: notcpp-0.0.1! http://hackage.haskell.org/package/notcpp [...] Why is it scopeLookup :: String - Q Exp with n bound to x :: T = @scopeLookup n@ evaluates to an Exp containing

Re: [Haskell-cafe] Understanding GC time

2012-03-12 Thread Steffen Schuldenzucker
On 03/10/2012 07:50 PM, Thiago Negri wrote: I see. Thanks for the answers. Any data structure or source annotation that would prevent that? For example, if I try the same program to run on a [1..] list, I'll get an out of memory error for the single-threaded version. Any way

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

2012-01-14 Thread Steffen Schuldenzucker
On 01/14/2012 03:55 PM, Ketil Malde wrote: Bryan O'Sullivanb...@serpentine.com writes: The question is a simple one. Must all operations on a TVar happen within *the same* atomically block, or am I am I guaranteed thread safety if, say, I have a number of atomically blocks in an IO function.

Re: [Haskell-cafe] named pipe interface

2012-01-12 Thread Steffen Schuldenzucker
On 01/12/2012 07:53 PM, Serge D. Mechveliani wrote: [...] For the to-A part writen in C (instead of Haskell), this interface loop works all right. With Haskell, I manage to process only a single string in the loop, and then it ends with an error. Main.hs is given below. I never dealt

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

2012-01-06 Thread Steffen Schuldenzucker
On 01/06/2012 11:16 AM, Steve Horne wrote: I was messing around with type-classes (familiarization exercises) when I hit a probably newbie problem. Reducing it to the simplest case... module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where -- n : node type -- d : data item type wrapped

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 WalkableBinTree n

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

2011-12-04 Thread Steffen Schuldenzucker
On 12/04/2011 06:53 AM, Scott Lawrence wrote: [...] Some operators might take more than one list/stream as an argument, combining them in some way or another. Obviously, if the lists were different lengths, the operator would fail. I don't want that to happen at run time, so I want to check for

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

2011-12-04 Thread Steffen Schuldenzucker
Hi Scott, a good idea. Why not use an existential to encode your types like myMap :: (a - b) - a-list of length n - b-list of length n myFilter :: (a - Bool) - a-list of length n - exists m. a-list of length m , where the first case is modeled using a type annotation and the second

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

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)

[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 nazarenko.ser...@gmail.com To: Steffen Schuldenzucker sschuldenzuc

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

2011-07-25 Thread Steffen Schuldenzucker
Hello Sergiy, On 07/25/2011 04:54 PM, Sergiy Nazarenko wrote: Hi, everyone! trycon - connect mysql bigtables vasya *** stmt' - query trycon INSERT INTO mytable (user,time,host,) VALUES (Vasya,2011.07.30 11.59,foo) I am beginner to use HSQL and I have a problem. I need to know row ID

Re: [Haskell-cafe] pointer equality

2011-07-21 Thread Steffen Schuldenzucker
On 07/21/2011 10:30 AM, Pedro Vasconcelos wrote: On Wed, 20 Jul 2011 12:48:48 -0300 Thiago Negrievoh...@gmail.com wrote: Is it possible to implement (==) that first check these thunks before evaluating it? (Considering both arguments has pure types). E.g., Equivalent thunks, evaluates to

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] Make Show instance

2011-07-21 Thread Steffen Schuldenzucker
Hi. On 07/21/2011 04:45 PM, Александр wrote: Hello, I have binary tree, with every leaf tuple - (k,v): data Tree k v = EmptyTree | Node (k, v) (Tree k v) (Tree k v) How can i make Show Instance for (Tree Int Int) ? The easiest way is automatic derivation: data Tree k v = EmptyTree |

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

2011-07-12 Thread Steffen Schuldenzucker
On 07/12/2011 05:01 PM, Ryan Newton wrote: Hi all, Is there something wrong with the code below? My anticipation was that the type of test would include the class constraint, because it uses the Assign constructor. But if you load this code in GHCI you can see that the inferred type was test

Re: [Haskell-cafe] class and instance

2011-07-10 Thread Steffen Schuldenzucker
On 07/10/2011 12:49 PM, Patrick Browne wrote: Hi, I am trying to understand the following code. I have written my current (mis-)understanding and questions below. I do not wish to improve the code, it is from a research paper[1] that I am trying to understand. Pat [1]

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

2011-07-06 Thread Steffen Schuldenzucker
Hi Markus, On 07/06/2011 03:04 PM, Markus Läll wrote: [...] import Control.Arrow import Control.Category type X a b = [a] - [b] instance Category X where id = map Prelude.id g . f = g Prelude.. f instance Arrow X where arr f = map f first f = unzip first f uncurry zip

Re: [Haskell-cafe] overloading show function

2011-06-29 Thread Steffen Schuldenzucker
Hi Philipp, On 06/29/2011 11:50 PM, Philipp Schneider wrote: Hi cafe, in my program i use a monad of the following type newtype M a = M (State - (a, State)) btw., it looks like you just rebuilt the State monad. ... instance (Show a,Show b) = Show (M (a,b)) where show (M f) = let

Re: [Haskell-cafe] Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker
On 06/26/2011 04:16 PM, michael rice wrote: MathWorks has the function seqperiod(x) to return the period of sequence x. Is there an equivalent function in Haskell? Could you specify what exactly the function is supposed to do? I am pretty sure that a function like seqPeriod :: (Eq a) =

[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 nowg...@yahoo.com To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de Hi Steffen, Repeating decimals. 5/7

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 nowg...@yahoo.com To: Steffen Schuldenzucker sschuldenzuc

Re: [Haskell-cafe] Hackage Server not reachable

2011-06-22 Thread Steffen Schuldenzucker
On 06/22/2011 11:02 AM, Stuart Coyle wrote: I cannot reach the hackage server so cabal can't download packages. Have I the correct address? http://hackage.haskell.org Yes. stuart@rumbaba:~# resolveip hackage.haskell.org http://hackage.haskell.org IP address of hackage.haskell.org

[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] Are casts required?

2011-06-06 Thread Steffen Schuldenzucker
Hi Patrick, On 06/06/2011 09:45 AM, Patrick Browne wrote: Are casts required to run the code below? If so why? Thanks, Pat -- Idetifiers for objects class (Integral i) = IDs i where startId :: i newId :: i - i newId i = succ i sameId, notSameId :: i - i - Bool -- Assertion is not

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

Re: [Haskell-cafe] Generating random graph

2011-04-10 Thread Steffen Schuldenzucker
Hello. I don't know if that is the reason for the strange behaviour, but On 04/11/2011 03:03 AM, Mitar wrote: I have made this function to generate a random graph for Data.Graph.Inductive library: generateGraph :: Int - IO (Gr String Double) generateGraph graphSize = do when (graphSize

Re: [Haskell-cafe] object oriented technique

2011-03-29 Thread Steffen Schuldenzucker
Tad, It doesn't look bad, but depending on what you want to do with the [ShapeD] aftewards you might not need this level of generality. Remember that the content of a ShapeD has type (forall a. ShapeC a = a), so all you can do with it is call class methods from ShapeC. So if all you do is

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

2011-02-23 Thread Steffen Schuldenzucker
Hi, On 02/23/2011 04:40 PM, Kurt Stutsman wrote: [...] Test is actually a kind of Serializable class. I don't want to restrict it to only working with Enums, which is what your OverlappingInstances seems to address. Is there a better way for doing what I am trying to do? Example: import

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] Synthetic values?

2011-02-09 Thread Steffen Schuldenzucker
In ghci I get let evil = appendLog Foo Bar interactive:1:11: Ambiguous type variable `p' in the constraints: `PRead p' arising from a use of `appendLog' at interactive:1:11-31 `PWrite p' arising from a use of `appendLog' at interactive:1:11-31 Probable fix:

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] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker
On 02/04/2011 12:36 PM, C K Kashyap wrote: Hi, I am looking for a way to extend GHCI such that I can do something like this $ 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.

Re: [Haskell-cafe] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker
Ok, so someFunction should modify the server's configuration? Maybe you can model it with an IORef like this (untested!): import Data.IORef type Config = String -- String to be prepended to every answer someFunction :: String - IORef Config - IORef Config someFunction s r = modifyIORef

[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

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] Typing problem

2011-01-31 Thread Steffen Schuldenzucker
Michael, just leaving out the type declaration for 'normalize', your module complies fine and ghc infers the following type: normalize :: (Integral a, Floating a) = [a] - a - a Note that the context (Integral a, Floating a) cannot be met by any of the standard types. (try in ghci: :i

Re: [Haskell-cafe] Inheritance and Wrappers

2011-01-31 Thread Steffen Schuldenzucker
On 01/31/2011 08:58 PM, MattMan wrote: [...] data Wrapper a = Wrap a instance (Num a) = AbGroup (Wrapper a) where add (Wrap i) (Wrap j) = Wrap(i+j) However, this is clumsy. Is there something else I can do? Thanks This is the normal approach. You can do funny things with the

Re: [Haskell-cafe] Instantiation problem

2011-01-29 Thread Steffen Schuldenzucker
Hi, Your definition of 'unit' in the instance MetricDescription LengthInCentimetres Centimetre is not well-typed. Maybe you want to write either unit (LengthInCentimitres 2.0) = Centimetre -- (pattern match fail for all (LengthInCentimetres l), l /= 2.0) or unit l = Centimetre -- i.e. unit

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

2011-01-26 Thread Steffen Schuldenzucker
On 01/26/2011 05:22 PM, Ozgur Akgun wrote: I working on a DSL represented by a algebraic data type with many constructors. I can write (separately) a parser and a pretty-printer for it, and I am doing so at the moment. However, this way it feels like repeating the same information twice. Is

[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] 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] 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
Hi Yves, On 11/01/2010 09:44 PM, Yves Parès wrote: Yes, I did make a small mistake in the type of eval. In fact, through the compiler messages, I guessed that it was a problem of matching between the 'rsc' type variable of runLoader and the 'rsc' of eval. I thought that this kind of matching

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] 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] in-equality type constraint?

2010-07-16 Thread Steffen Schuldenzucker
On 07/17/2010 01:08 AM, Paul L wrote: Does anybody know why the type families only supports equality test like a ~ b, but not its negation? This has annoyed me, too. However, HList provides something quite similar, namely the TypeEq[1] fundep-ed class which will answer type-equality with a

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

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

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

2010-07-05 Thread Steffen Schuldenzucker
Dear Cafe, since a little discussion with my tutor I am wondering how the following problem can be solved and if it is decidable: Given the definition of a recursive function f in, say, haskell, determine if f can be implemented in O(1) memory. First I thought the solution would be check

Re: [Haskell-cafe] More experiments with ATs

2010-07-04 Thread Steffen Schuldenzucker
On 07/04/2010 01:49 PM, Sjoerd Visscher wrote: On Jul 4, 2010, at 11:31 AM, Andrew Coppin wrote: type family F f a :: * class RFunctor f where (%) :: f a b - (a - b) - F f a - F f b I have literally no idea what a type family is. I understand ATs (I think!), but TFs make no

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

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

2010-06-01 Thread Steffen Schuldenzucker
Dear Cafe, let: data True data False class C a (arbitrary instances for C may follow) Now, how to obtain an Indicator Type for C, i.e. a type IndC that is defined via a type family / fundep / ... , so that IndC a = True forall a which are instances of C IndC a = False for all other a.

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

Re: [Haskell-cafe] Ada-style ranges

2010-04-26 Thread Steffen Schuldenzucker
On 04/26/2010 12:50 PM, hask...@kudling.de wrote: Hi list, how would you describe Ada's ranges in Haskell's typesystem? http://en.wikibooks.org/wiki/Ada_Programming/Types/range Hi Lenny, can non-constant expressions be given as arguments to 'range'? If not, then what about a

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

2010-03-08 Thread Steffen Schuldenzucker
On 03/08/2010 10:45 PM, Wolfgang Jeltsch wrote: The point is, of course, that such conversions are not only possible for binary operations but for arbitrary values and that these conversions are done by a single generic function conv. I don’t think it would be possible to implement conv

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

2010-01-22 Thread Steffen Schuldenzucker
Hi Andrew, Andrew U. Frank wrote: here a simplistic case (i know that A could be reduced to [], my real cases are more complicated). data A b = A b [b] data Asup x ab y = Asup x ab y class X a b where push :: b - a b - a b instance X A Int where push b' (A b bs) = A b' (b:bs)

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] lawless instances of Functor

2010-01-04 Thread Steffen Schuldenzucker
Hi Paul, Paul Brauner wrote: Hi, I'm trying to get a deep feeling of Functors (and then pointed Functors, Applicative Functors, etc.). To this end, I try to find lawless instances of Functor that satisfy one law but not the other. I've found one instance that satisfies fmap (f.g) = fmap f

Re: [Haskell-cafe] Partially applied functions

2009-11-28 Thread Steffen Schuldenzucker
Ozgur Akgun wrote: Hi cafe, Is such a thing possible, add :: Int - Int - Int add x y = x + y -- a list of partially applied functions adds = [add 3, add 5, add 7, add 3, add 5, add 8] -- an example usage of the list k = map (\ f - f 10 ) adds add3s = filter (?) adds -- add3s =

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] Ghci :ctags or hasktags print to standard out instead of file

2009-10-10 Thread Steffen Schuldenzucker
The TagList plugin for Vim reads the ctags info from the command line instead of from the file. I could not figure out how to make ghci :ctags or hasktasks to print the ctags info to the command line. Is there a way to do that? Any hints? Hmm... some shell magic: mkfifo foo cat foo echo

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

2009-05-18 Thread Steffen Schuldenzucker
On 16:25 Mon 18 May , Gü?nther Schmidt wrote: Hi all, I'm trying to express a constraint using a data structure. Let's say I'd want to express a mapping of a to b, c to b, d to b and e to f. A mapping can also be from a to a, b to b and so on. The constraint is that one cannot map a

Re: [Haskell-cafe] Haskell Arrows Applications

2009-05-06 Thread Steffen Schuldenzucker
On 07:33 Wed 06 May , Hannousse wrote: Hello, I'm interested to the concept of arrows in Haskell, however, I couldn't find a real application or example using this new technology in a real world application. All what I found are just academic examples and other people developing new

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

2009-04-28 Thread Steffen Schuldenzucker
On 22:19 Mon 27 Apr , Martijn van Steenbergen wrote: Tillmann Rendel wrote: Achim Schneider wrote: In other words: 1) Explain Pointed 2) Explain Functor 3) Explain Applicative 4) Explain Monad Why Pointed first? Functor seems more useful and more basic. They are in order of power:

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

2009-04-28 Thread Steffen Schuldenzucker
On 04:33 Tue 28 Apr , Matthew Gruen wrote: On the other hand, here's an un-pure-able and un-point-able functor: instance Functor ((,) m) where   --fmap :: (n - n') - (m, n) - (m, n')     fmap f (m, n) = (m, f n) n - (m, n) is not a function you can write in general

[Haskell-cafe] HXT: desperatedly trying to concat

2009-04-02 Thread Steffen Schuldenzucker
Hi. I've got a problem with the Haskell XML Toolkit (hxt). I want to write a little app that performs REST requests from a certain (rather simple) XML format. A example procedure Call looks like testData defined below. What I'd like to do is to transform this xml tree into a GET variable string

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

2009-04-02 Thread Steffen Schuldenzucker
Hello again. I finally got it myself. It was just a matter of parentheses: See http://hpaste.org/fastcgi/hpaste.fcgi/view?id=3229 for the corrected version. Looks like what I was trying to do is not expressable via just an arrow, one needs a function mapping the input arrow to a new one. I'm