[Haskell-cafe] GUIs, FRP, (Delimited) Continuations and Zippers

2009-05-19 Thread oleg
Could either of those approaches (FRP / Delimited Continuations) be a solution for implementing complex GUI code? I think the answer is generally yes; I have tried writing a user interface which has a form with several controls; a change in one control may affect all other controls on the form

[Haskell-cafe] Re: Using Takusen is a real intellectual challenge

2009-05-04 Thread oleg
Perhaps you might find the following code, relying on low-level Takusen's functions, useful http://darcs.haskell.org/takusen/Database/PostgreSQL/Test/pgaccess.hs The code is a stand-alone program that does the following: docstrings = [ A helper to access a PostgreSQL from a

Re: [Haskell-cafe] Lazy vs correct IO [Was: A round of golf]

2009-04-05 Thread oleg
It opens and closes each file in turn; but it would it be unwise to open and close each file as we'd read a chunk from it? This would allow arbitrary interleaving. If I understand you correctly, you are proposing processing several files in parallel, so to interleave IO. If the `files'

[Haskell-cafe] Problem with prepose.lhs and ghc6.10.1

2009-04-03 Thread oleg
../haskell/prepose.lhs:707:0: Parse error in pattern which is pointing at: normalize a :: M s a = M (mod a (modulus (undefined :: s))) The code indeed used lexically scoped type variables -- which GHC at that time implemented differently. Incidentally, on the above line, M s a is the type

[Haskell-cafe] Zippers from any traversable [Was: Looking for practical examples of Zippers]

2009-04-01 Thread oleg
wren ng thornton wrote: how, for instance, turn a nested Map like Map Int (Map Int (Map String Double) into a zipped version. You can't. Or rather, you can't unless you have access to the implementation of the datastructure itself; and Data.Map doesn't provide enough details to do

[Haskell-cafe] typeOf for polymorphic value

2009-03-25 Thread oleg
Does anyone know of a trick to accomplish `typeOf id'? Using something else than TypeRep as the representation, of course. Yes. The analysis of polymorphic types has been used in the inverse type-checker http://okmij.org/ftp/Haskell/types.html#de-typechecker The enclosed code computes

[Haskell-cafe] Typing Dynamic Typing [Was: Dynamically typing TH.Exp at runtime]

2009-03-12 Thread oleg
Martin Hofmann asked: Is there a Haskell implementation of the paper Typing Dynamic Typing by Baars and Swierstra There is a different implementation but in the same spirit http://okmij.org/ftp/tagless-final/IncopeTypecheck.hs

[Haskell-cafe] Re: Type families not as useful over functions

2009-02-12 Thread oleg
John Ky wrote: Is there a way to define type r to be all types except functions? Perhaps the following article How to write an instance for not-a-function http://okmij.org/ftp/Haskell/typecast.html#is-function-type answers your question. It shows several complete examples.

[Haskell-cafe] Painting logs to get a coloured tree

2009-02-10 Thread oleg
If I understand you correctly, the problem is to annotate an already constructed tree with arbitrary pieces of new data -- hopefully without reconstructing the tree. Perhaps the approach used in the FLOLAC type-checkers would be helpful. The `tree' was an expression in lambda-calculus to type

[Haskell-cafe] Re: type metaphysics

2009-02-02 Thread oleg
I believe the original notion of type by Russell is most insightful, bridging the semantic notion of type (type as a set of values) and the syntactic notion (type system as a syntactic discipline, a statically decidable restriction on terms). That point is discussed at some length in Sec 3 (pp.

[Haskell-cafe] Re: Updating doubly linked lists

2009-01-03 Thread oleg
Stephan Guenther wrote: Is it possible to change a particular node of the doubly linked list? That is to say, that would like to have a function: update :: DList a - a - DList a where update node newValue returns a list where only the value at the node which is passed in is set to the new

[Haskell-cafe] Re: understanding enumerator/iteratee

2008-12-23 Thread oleg
Artyom Shalkhakov wrote I would say that it [iteratee] just tells us how to react to various forms of input. :) This is much like the function you pass to foldr. Precisely. To sum up all elements of Data.Map, we do Map.fold (+) 0 mp to sum up all elements of a set we do

[Haskell-cafe] The Knight's Tour: solutions please

2008-12-02 Thread oleg
Yes, there is a solution for n=99 and for n=100 for that matter -- which can be found under one second. I only had to make a trivial modification to the previously posted code tour n k s b | k n*n = return b | otherwise = do next - (foldr mplus mzero).map return $ successors

[Haskell-cafe] The Knight's Tour: solutions please

2008-11-30 Thread oleg
It seems the following pure functional (except for the final printout) version of the search has almost the same performance as the Dan Doel's latest version with the unboxed arrays and callCC. For the board of size 40, Dan Doel's version takes 0.047s on my computer; the version below takes

[Haskell-cafe] Instances that shouldn't overlap

2008-11-26 Thread oleg
Paul Johnson wrote: class (Eq a) = AppEq f a where instance (Applicative f, Eq a) = AppEq f a where instance (Ord a) = AppEq Interval a where In Haskell, instances are selected based solely on the types in the head. Constraints like `Applicative f' are not consulted when the instance is

[Haskell-cafe] Monadic bind with associated types + PHOAS?

2008-11-18 Thread oleg
Ryan Ingram wrote: One thing that often comes up is a desire to do a pass on the resultant code to optimize it, but it's pretty difficult with the standard monadic formulation because of embedded functions. You can't do introspection on functions in Haskell; they aren't elements of Eq or

[Haskell-cafe] Closed type classes [was: Exporting a Type Class for Type Signatures]

2008-11-10 Thread oleg
Dominic Steinitz wrote: In the crypto package, I have two functions encrypt :: AESKey a = a - Word128 - Word128 decrypt :: AESKey a = a - Word128 - Word128 but the class AESKey is not exported, to prevent the user from adding more instances to it. Since AESKey is not exported, the users

[Haskell-cafe] reliable (bi)directional pipe to a process

2008-11-10 Thread oleg
I'd like to point out a reliable, proven and simple way of interacting with another process, via unidirectional or bidirectional pipes. The method supports Unix sockets, pipes, and TCP sockets. I too have noticed insidious bugs in GHC run-time when communicating with another process via a pipe.

[Haskell-cafe] Typeable and Dynamic

2008-11-03 Thread oleg
minh thu asked a tricky question, about writing extract :: Typeable a = TypeRep - Dynamic - a The question here is what determines the type 'a'. One answer is that 'a' is determined from the context, e.g., (extract tr dyn) + 1.0 fixes 'a' to be an Int. In that case, extract is

[Haskell-cafe] Re: labels in HList

2008-10-22 Thread oleg
It seems that a couple of modules in HList libraries didn't have enough LANGUAGE pragmas (in one case, GHC 6.8.3 started to require ScopedTypeVariables where the previous version of GHC did not). Cabal and OOHaskell supply all needed extensions on the command line, and so see no problems. I have

Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-16 Thread oleg
Lennart Augustsson wrote: We don't need them [existentials] from a theoretical perspective, but in practice I'd rather use existentials than encodinging them in some tricky way. If the claim that we don't need existentials theoretically is obvious, I don't have the argument. Still,

[Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread oleg
Lennart Augustsson wrote: I was just pointing out that the mechanism for doing the OO thing exists in Haskell too, albeit looking a little different. Indeed there is a mechanism for doing OO in Haskell -- several of them. Most of them have nothing to do with Existentials. In the OHaskell

[Haskell-cafe] Class Quantification

2008-10-01 Thread oleg
Bas van Dijk wrote: ... it's possible to define 'foo' and 'bar' like so: foo :: (Num c, Num d) = (forall b. Num b = a - b) - a - (c, d) foo f x = (f x, f x) bar :: (Read c, Read d) = (forall b. Read b = a - b) - a - (c, d) bar f x = (f x, f x) Which allows us to write: testFoo =

[Haskell-cafe] Restricted file reading monad

2008-10-01 Thread oleg
George Pollard wrote: The structure of an ID3 tag goes something like this: Header: - total size of tag - other header info A series of frames, each with: - total size of frame - other header info - frame data Since the ID3 tag as a whole has size information, I need to pass that into

[Haskell-cafe] Iteratee-based IO

2008-09-20 Thread oleg
brian wrote: I want to use Parsec to parse NNTP data coming to me from a handle I get from connectTo. One unworkable approach I tried is to get a lazy String from the handle with hGetContents. It seems there is another approach, which is neither unsafe nor imperative. It relies neither on

[Haskell-cafe] Lazy vs correct IO [Was: A round of golf]

2008-09-19 Thread oleg
Lennart Augustsson wrote main = do name:_ - getArgs file - readFile name print $ length $ lines file Given the stance against top-level mutable variables, I have not expected to see this Lazy IO code. After all, what could be more against the spirit of Haskell than a `pure'

[Haskell-cafe] Re: Strongly Typed Memory Areas

2008-09-18 Thread oleg
John Van Enk wrote: Was Iavor/Mark's paper ever implemented as a GHC extension? Strongly Typed Memory Areas It turns out most of the functionality is already available in Haskell: Lightweight static resources, for safe embedded and systems programming

[Haskell-cafe] Re: number-parameterized types and heterogeneous lists

2008-06-23 Thread oleg
Luke Palmer wrote in response to Harald ROTTER I also wonder if there is some kind of generalized foldr such that, e.g. D1 $ D0 $ D0 $ Sz = specialFoldr ($) Sz [D1,D0,D0] I think that this foldr must be some special foldr that augments the data type of the result in each foldr step.

[Haskell-cafe] Re: Trying to avoid duplicate instances

2008-05-14 Thread oleg
Eric Stansifer wrote: I am using a bunch of empty type classes to categorize some objects: class FiniteSolidObject o class FinitePatchObject o class InfiniteSolidObject o Since solid objects are exactly finite solid objects plus infinite solid objects, there is an obvious way to code

[Haskell-cafe] Monad instance for Data.Set

2008-03-24 Thread oleg
The following code solves exactly the problem of implementing (restricted) MonadPlus in terms of Data.Set: http://okmij.org/ftp/Haskell/DoRestrictedM.hs The code is written to demonstrate the do-notation. We write the monadic code as usual: test1s_do () = do x - return a return

[Haskell-cafe] Re: Reflective capabilities of Haskell (cont'd)

2008-03-13 Thread oleg
Martin Hofmann wrote: Thanks a lot, this helps a bit, but access to function bodies is exactly what I need. Then perhaps you might like the method of reconstructing bodies (of possibly compiled) functions http://okmij.org/ftp/Computation/Generative.html#diff-th in the form of AST --

[Haskell-cafe] Instance selection based on a class constraint [was: Issues(Bugs?) with GHC Type Families]

2008-03-11 Thread oleg
Manuel M T Chakravarty: Hugo Pacheco: I would simply like the compiler not to use that instance if the equality constraint does not hold, like some another instance dependency constraint, but I assume that is not possible. This is independent of type families. The selection of type

[Haskell-cafe] Exception handling when using STUArray

2008-03-11 Thread oleg
Sterling Clover wrote: there's no standard way that I know of besides inspection to determine if code might throw an exception, and this is particularly the case with the dreaded lazy IO of prelude functions. The following old message showed even two ways of doing exactly that -- in Haskell,

[Haskell-cafe] Haskell w/ delimited continuations

2008-02-23 Thread oleg
Call-by-name lambda-calculus is strictly more expressive (in Felleisen sense) than call-by-value lambda-calculus, and the call-by-need (aka, lazy) lambda-calculus is observationally equivalent to the call-by-name. One can add shift/reset to any of these calculi (CBV shift/reset is most known;

[Haskell-cafe] Designing DSL with explicit sharing [was: I love purity, but it's killing me]

2008-02-14 Thread oleg
Matthew Naylor wrote: it's not immediately clear (to me at least) how efficient your method will be in practice. Any method based on common sub-expression elimination surely must inspect every node in the flattened graph. In the worst case, an acyclic graph containing n nodes could have 2^n

[Haskell-cafe] Designing DSL with explicit sharing [was: I love purity, but it's killing me]

2008-02-13 Thread oleg
Tom Hawkins wrote: ] My DSLs invariably define a datatype to capture expressions; something ] like this: ] ] data Expression ] = Add Expression Expression ] | Sub Expression Expression ] | Variable String ] | Constant Int ] deriving Eq ] The problem comes when I want to generate

[Haskell-cafe] Re: HList error with hFoldr

2008-01-27 Thread oleg
After some fooling around, I came up with something I think makes sense. Let me know if this is the right/wrong thing. It seems to work for the examples I've tried so far. instance (Floating f, MetricSpace e f ,MetricSpace e' f, HZip l l (HCons (e', e') l') ,HFoldr

[Haskell-cafe] Re: Applying a Dynamic function to a container of Dynamics

2007-12-22 Thread oleg
Alfonso Acosta wrote: dynApp allows to apply a Dynamic function to a Dynamic argument: dynApp :: Dynamic - Dynamic - Dynamic I don't seem to find a way (without modifying Data.Dynamic itself) to code this function This is not very difficult if we have a well-delineated (and still infinite)

[Haskell-cafe] Dynamic typing of polymorphic functions

2007-12-20 Thread oleg
Alfonso Acosta wrote: mapSY :: (Typeable a, Typeable b) = (a - b) - Signal a - Signal b mapSY f (Signal primSig) = Signal (PrimSignal (MapSY (toDyn f) primSig)) The following process would be really useful but its compilation obviously fails: mapSnd :: Signal (a, a) - Signal a mapSnd =

[Haskell-cafe] Re: type trickery

2007-12-20 Thread oleg
Adrian Neumann wrote: I figured I'd need something like this data GF = GF Integer Integer so that each element of the finite field would remember p. However I can't think of a way to use the typesystem to ensure that p is always the same. You might like: Vectro: Haskell library

[Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread oleg
Philipp N. wrote: i'm trying to wrap functions (a - b - ... - z) of any arity to functions of type ([String] - y), where list of strings replaces the typed arguments. the problem is, that you cannot distinguish type (x-y) from z, so these instances are overlapping. to which apfelmus replied

[Haskell-cafe] Re: Guidance on using asynchronous exceptions

2007-11-16 Thread oleg
Yang wrote: Furthermore, is there any way to embed this information [about async execptions] in the type system, so that Haskellers don't produce async-exception-unaware code? (Effectively, introducing checked interrupts?) Yes, it is possible to make the information about exceptions and

[Haskell-cafe] Implementing the State Monad

2007-11-11 Thread oleg
apfelmus showed the implementation of the state monad as free term algebra, using GADT. Here's an implementation that does not use GADT http://okmij.org/ftp/Haskell/types.html#state-algebra All the smarts are in the observation function. This style is _very_ well explained by Ralf Hinze

[Haskell-cafe] Typed DSL compiler, or converting from an existential to a concrete type

2007-10-06 Thread oleg
The earlier message showed how to implement a typechecker from untyped AST to wrapped typed terms. The complete code can be found at http://okmij.org/ftp//Haskell/staged/TypecheckedDSL.hs The typechecker has the type typecheck :: Gamma - Exp - Either String TypedTerm where

[Haskell-cafe] Typechecker to GADT: the full implementation of a typed DSL

2007-10-04 Thread oleg
Pasqualino 'Titto' Assini wrote: I am trying to write an interpreter for a little functional language but I am finding very problematic to dynamically create a typed representations of the language terms. The problem is to write a function that converts between Exp and Term t as in:

[Haskell-cafe] Parser inversions [Was: CC-delcont-0.1...]

2007-08-01 Thread oleg
Dan Doel wrote about `inverting' a parser -- first, a pure parser consuming a string and later a parser written in a monadic style and consuming a monadic list: data MList' m a = MNil | MCons a (MList m a) type MList m a = m (MList' m a) The second attempt proved fully successful: So,

[Haskell-cafe] Takusen and large PostgreSQL blobs [was: Handling custom types in Takusen]

2007-07-27 Thread oleg
I have been using Takusen with PostgreSQL to store and retrieve hundreds of multi-megabyte binary objects. A client may request literally hundred of such objects in one request; the Haskell (FastCGI) application server will send these objects in one multi-part message. The handling of the entire

[Haskell-cafe] Re: hMapping polymorphic functions

2007-07-17 Thread oleg
hMapping polymorphic functions is indeed quite challenging, but can be done. That was the topic of the message Type-class overloaded functions: second-order typeclass programming with backtracking http://okmij.org/ftp/Haskell/poly2.txt The challenge is how to avoid

Re: [Haskell-cafe] Two-continuation `monads' and MonadMinus

2007-07-07 Thread oleg
I was initially skeptical about defining Foldable for the direct-style LogicT transformer, but now I suspect that it is definable. Now that I think about it, you're losing the ability to work with monad transformers. I think you're right. The particular point of msplit is that it is a monad

[Haskell-cafe] Lightweight sequent calculus and linear abstractions

2007-07-05 Thread oleg
Conor McBride has posed an interesting problem: implement constructors P v for embedding pure values v Ofor holes f :$ a for application, left-associative and an interpreting function emmental such that emmental (P (+) :$ (P (*) :$ O :$ P

Re: [Haskell-cafe] folds with escapes

2007-07-05 Thread oleg
Can you do dropWhile in terms of foldr? One can write foldr that represents drop or dropWhile of the original foldr. One can do even more: zip two folds. That is, obtain a fold that is equivalent to zipping up two lists represented by the original folds. Even furthermore, one can do all these

[Haskell-cafe] Re: Playing with delimited continuations

2007-07-05 Thread oleg
The ZFS library contains the most up-to-date implementation of the CC monad and the transformer. I have a few other versions scattered around, but they are probably not relevant. I found the CC_FrameT.hs to be the fastest one. Is that you can think of normal continuations as delimited

[Haskell-cafe] Two-continuation `monads' and MonadMinus [Re: Parsers are monadic?]

2007-07-03 Thread oleg
When designing the full Kanren, we have experimented with two-continuation actions and various plumbing combinators (any, all, deterministic-all, etc). We eventually gave up on this after we realized that a simple interface suffices. Called MonadMinus, it is capable of defining LogicT monad with

[Haskell-cafe] Re: practicality of typeful programming

2007-06-27 Thread oleg
Daniil Elovkov wrote: The fact that structure is mixed with properties seems to put some limits on both doability and, even more, practilaty of encoding complex properties. That's why phantom types, attached via a newtype wrapper, are so appealing. If we remove the wrapper, we get the

[Haskell-cafe] Re: copy-on-write monad?

2007-06-23 Thread oleg
Greg Meredith wrote: First, has anyone worked out a monadic approach to copy-on-write? (And, Is there any analysis of perf characteristics of said monadic schemes?) If you use Zippers (Huet's or generic ones) with functional updates, copy-on-write comes out automatically and by default. This

[Haskell-cafe] Re: practicality of typeful programming

2007-06-16 Thread oleg
Daniil Elovkov wrote: I've recently asked some questions here about some little type hackery implementing an embedded dsl. But now I wonder if it's worth the effort at all... Yes it is. Typed embedded DSL are quite useful and widely used. For example, Lava (high-level hardware description

[Haskell-cafe] lists with mixed types

2007-06-16 Thread oleg
Anatoly Yakovenko wrote: but what i really want to do is just do map func [1, 2.0] [1, 2.0] I understand that this is impossible in haskell, If you use a heterogeneous list, it is possible. The HList paper describes such examples. http://homepages.cwi.nl/~ralf/HList/ but why

[Haskell-cafe] Re: HList questions

2007-06-10 Thread oleg
Marc Weber wrote: Do you know what a type indexed coproduct is ? (TIC.hs from HList) What is the purpose of this module? In a regular Haskell record, we can retrieve the value of one of its components given the label. A type-indexed Product (TIP, or TIR) is a similar collection of values --

Re: [Haskell-cafe] Re: Has anyone looked into adding subtyping...

2007-06-02 Thread oleg
The last time I tried this code, I reported to haskell-cafe that OOHaskell does not work when compiled as a library (at least under GHC). For some reason the code that uses OOHaskell had to be compiled along side it. Is this now fixed? It may be, I have to try. It should be mentioned that

Re: [Haskell-cafe] Implementing Mathematica

2007-05-31 Thread oleg
Jon Harrop wrote: However, I can't think how you might return physically identical results when possible in Haskell. Perhaps you might be interested then in the following function that non-destructively updates a subterm in a large term, preserving sharing. The function can be used to do a

[Haskell-cafe] Re: equations and patterns

2007-05-31 Thread oleg
mingli yuan wrote: Seems mathematic axioms and pattern matching are different things. So how could I rewrite the equations to pattern matching? Which technique should I learn? Haskell is more suitable for re-writing systems, which are based on oriented equations. The question of orientation

[Haskell-cafe] Re: Has anyone looked into adding subtyping to Haskell?

2007-05-31 Thread oleg
Polymorphic extensible records with subtyping are already expressible in Haskell. There is nothing needs to be added: http://homepages.cwi.nl/~ralf/HList/ http://homepages.cwi.nl/~ralf/OOHaskell/ The full code is available via darcs http://darcs.haskell.org/OOHaskell/

[Haskell-cafe] GADT and typeclasses [was: Language extensions]

2007-05-27 Thread oleg
Philippa Cowderoy wrote: For example, GADTs let you implement monads as interpreters by defining a datatype representing the abstract syntax tree that describes a computation - you can't get this to type without at a minimum existential types and for many monad operations you need the full

[Haskell-cafe] Re: Type class help please

2007-05-16 Thread oleg
Adrian Hey wrote: -- Instances of GT are instances of Eq -- instance (GT map key, Eq a) = Eq (map a) where map1 == map2 = assocsAscending map1 == assocsAscending map2 ... Overlapping instances for Eq [(key, a)] arising from use of `==' at Test.hs:10:16-59 Matching

[Haskell-cafe] Re: Type class help please

2007-05-16 Thread oleg
Also, I suspect I'm still missing something important here, for example I don't understand why, if it overlaps for [], it doesn't overlap with other instances (like Maybe for example). Or am I just not getting the error for Maybe because ghc stops after the first error? One may think of

[Haskell-cafe] Re: a question concerning type constructors

2007-05-07 Thread oleg
In Haskell, is it possible to declare a type constructor with a variable number of type variables e.g. data Tuple * allowing the following declarations: t: Tuple u: Tuple Bool v: Tuple Bool Int w: Tuple Bool Int Char Although the data constructor such as the `Tuple' is not

[Haskell-cafe] Re: Monad definition question

2007-05-05 Thread oleg
Ilya Tsindlekht wrote: Does the definition of monad silently assume that if f and f' are equal in the sense that they return the same value for any argument o correct type then m = f = m = f' Of course NOT! Here's an example, in a State monad f x = put True f' x = put False

[Haskell-cafe] Re: Monad definition question

2007-05-05 Thread oleg
Ilya Tsindlekht wrote It may be useful to relate to imperative programming: m1 = (\x - m2) is let x = m1 in m2 The analogy is not always straight-forward - try the list monad. This equivalence holds even for the List Monad. Here is an example of non-determinism:

[Haskell-cafe] Type-level programming problem

2007-04-30 Thread oleg
Thomas Schilling wrote: data T class Foo ns a b c | ns - a, ns - b, ns - c where mkFoo :: ns defaultA :: a defaultB :: c - IO b defaultC :: [T] - c f :: c - b - a - (b, Int) data DefaultA instance Foo ns a b c = Apply DefaultA ns a where apply _ _ =

[Haskell-cafe] Re: haskell question

2007-04-22 Thread oleg
Is there documentation on the multi-parameter type classes? Sections 7.4.2. Class declarations, 7.4.3 Functional dependencies and 7.4.4. Instance declarations of the GHC user guide give the short description of these features. These section refer to a couple of papers. The best explanation can

[Haskell-cafe] Re: haskell question

2007-04-20 Thread oleg
Greg Meredith wrote: The file compiles with ghc as is. If you uncomment the last section, however, you see that to close the loop on the constraints for the agent syntax we hit a typing error. i bithink/i/b this is a hard constraint in Haskell that prevents this level of generality in the

[Haskell-cafe] Re: Type classes and type equality

2007-04-19 Thread oleg
- If we permit overlapping instances extension, then a few lines of code decide equality for all existing and future types: class TypeEq x y b | x y - b instance TypeEq x x HTrue instance TypeCast HFalse b = TypeEq x y b This is exactly what I was after, but

[Haskell-cafe] Re: Type classes and type equality

2007-04-17 Thread oleg
Thanks for pointing that out. As far as I can see, this requires a new instance declaration for every type? I guess it depends on how many extensions one may wish to enable. At the very least we need multi-parameter type classes with functional dependencies (because that's what TypeEq is in

[Haskell-cafe] implementing try for RWST ?

2007-04-16 Thread oleg
The examples presented so far seem to show that the computation will eventually run in the IO monad. One may wonder then why do we need RWST transformer, given that the IO monad can implement both the state and writer. At the very least me need the reader transformer, which is the least demanding

[Haskell-cafe] Matlab in Haskell

2007-04-11 Thread oleg
Ryan Dickie wrote: I also hate matlab to death. Is there any possibility of using haskell as a replacement using ghci? Yes. The strongly typed linear algebra project (Vectro) does exactly that. With an added guarantee that attempting to add or multiply matrices of inappropriate sizes is a type

[Haskell-cafe] Re: Type error

2007-04-10 Thread oleg
Alfonso Acosta wrote: I tried the existential approach when it was previously suggested by Chris, but the problem is that, for some Source instances calling methods from HDPrimType within supplySig is not enough. Thus, it doesn't work with existentials due to their limitations. I see. The

[Haskell-cafe] Re: Type error

2007-04-08 Thread oleg
Alfonso Acosta wrote: I have a type problem in my code which I dont know how to solve data HDSignal a = HDSignal class HDPrimType a where class PortIndex a where class SourcePort s where -- Plug an external signal to the port plugSig :: (HDPrimType a, PortIndex ix) =ix - s -(HDSignal

[Haskell-cafe] Re: A question about functional dependencies and existential

2007-03-28 Thread oleg
class T root pos sel | pos - root, root - sel where f :: pos - sel - Bool instance T root (Any root) sel But the same applies to the second functional dependency and the type variable sel. Every instantiation of root determines the instantiation of sel. And that forbids instance T Int

[Haskell-cafe] Re: A question about functional dependencies and existential

2007-03-27 Thread oleg
Jean-Marie Gaillourdet wrote: class T root pos sel | pos - root, root - sel where f :: pos - sel - Bool instance T root (Any root) sel If that is correct, I don't understand why this instance should be to general, as every instantiation of root exactly determines the corresponding

[Haskell-cafe] A question about functional dependencies and existential quantification

2007-03-26 Thread oleg
Jean-Marie Gaillourdet wrote I am trying to do something like the following: {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-} module TestCase where data Any root = forall pos sel . T root pos sel = ANY pos class T root pos sel | pos - root, root - sel where f :: pos

[Haskell-cafe] Re: There can be only one fix? Pondering Bekic's lemma

2007-03-19 Thread oleg
Nicolas Frisby wrote: My question is: Given products and a fixed point combinator, can any pure expression be transformed into a corresponding expression that has just a single use of fix? Albert Y. C. Lai pointed out model-theoretical and CPU-practical answers. There is also a

Re: lazily handling exceptions in lazy sources (Re: [Haskell-cafe] Re:

2007-03-15 Thread oleg
the usual caveats about unsafePerformIO apply, so perhaps you wouldn't want to use this in a database library.. Indeed. This is quite problematic, from the practical point of view of making resources difficult to control (cf. another thread of file handle leakage), to the theoretical point

[Haskell-cafe] Lack of expressiveness in kinds?

2007-03-15 Thread oleg
Andrew Wagner wrote data Foo a = Bar a data (Ord a) = Baz a = Bah a Note that both of these have kind * - *. However, Baz could never be an instance of monad, because there is a restriction on the types it can operate on. There is a wide-spread opinion that one ought not to give context to

Re: [Hs-Generics] FW: [Haskell-cafe] SYB vs HList (again)

2007-03-15 Thread oleg
[Please follow-up to [EMAIL PROTECTED] S. Alexander Jacobson wrote: HLists require you to define Labels and basically only use label values that are themselves either scalar or HLists. ... With SYB you create field labels using newtype (or data) declarations e.g. data Salary = S

[Haskell-cafe] How do I avoid stack overflows?

2007-03-15 Thread oleg
DavidA wrote: I'm trying to write some code which involves lots of matrix multiplications, but whenever I do too many, I get stack overflows (in both GHCi 6.4.2, and Hugs May 2006). By placing a couple of strictness annotations, your test' gives the expected answer (given some time) on Hugs.

[Haskell-cafe] Maybe and partial functions

2007-03-13 Thread oleg
Neil Mitchell wrote: I suggest you try rewriting this program to be complete: http://darcs.haskell.org/nofib/imaginary/digits-of-e2/Main.lhs (if you do, please post the result to the list) As Gen Zhang noted, the problem seems to be quite straightforward: just express in types the fact

[Haskell-cafe] Re: Maybe and partial functions

2007-03-13 Thread oleg
Neil Mitchell wrote: newtype N1 = N1 Int (put that in a module and don't export N1) define the constant 2, define the increment operator, change div and mod. That is precisely what I would have done. Now we've mainly got a proof in the type checker, but we still don't actually have a

[Haskell-cafe] Takusen and strictness, and perils of getContents

2007-03-02 Thread oleg
Takusen permits on-demand processing on three different levels. It is specifically designed for database processing in bounded memory with predictable resource utilization and no resource leaks. But first, about getContents. It has been mentioned a while ago that getContents should be renamed to

[Haskell-cafe] Re: overlapping instances, selecting if type a does not belong to class?

2007-02-27 Thread oleg
uses the results of the analysis. I wasn't able to find the definition of AllOf(But): It is in the complete code http://pobox.com/~oleg/ftp/Haskell/poly2.hs It isn't that interesting: data AllOfBut x y {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances

[Haskell-cafe] overlapping instances, selecting if type a does not belong to class?

2007-02-26 Thread oleg
complaint. That said, it is quite possible in Haskell to achieve genuine class-based dispatch, with backtracking if necessary: http://pobox.com/~oleg/ftp/Haskell/poly2.txt However, it seems that your particular problem can be solved with simpler means: instance (HList

[Haskell-cafe] Safe lists with GADT's

2007-02-26 Thread oleg
Stefan O'Rear wrote: Personally I like the GADT approach best since it is very flexible and convienient. I have never used a purpose-build computer proof system, but (modulo _|_) it took me less than 10 minutes to answer LoganCapaldo (on #haskell)'s challenge to proof that + was commutative

[Haskell-cafe] OO Design in Haskell Example (Draft)

2007-02-26 Thread oleg
Steve Downey wrote: In the last OO design in Haskell thread (and probably in every one preceeding it), it was suggested that having some examples might be a good idea. Since most people with existing designs will have some familiarity with Design Patterns, and those are typical building

[Haskell-cafe] Re: Code and Perf. Data for Prime Finders

2007-02-23 Thread oleg
Perhaps you might want include in your test the following: http://www.haskell.org/pipermail/haskell-cafe/2007-February/022437.html It seems quite close to the genuine Eratosthenes sieve algorithm: it employs the idea of marks, it can cross composite numbers off several times, and it never

[Haskell-cafe] Type-level lambdas in Haskell?

2007-02-21 Thread oleg
On 2/21/07, Alfonso Acosta alfonso.acosta at gmail.com wrote: In my opinion adding Type-level lambdas would be the way to go, but they unfortunately are not part of Haskell. Type-level lambdas are already present in Haskell. Please see the messages On computable types. I. Typed lambda and

[Haskell-cafe] Type-level lambdas in Haskell? ( was Multiparameter class error)

2007-02-21 Thread oleg
Alfonso Acosta wrote: class Synchronous s f1 f2 | s - f1, s - f2 where mapSY :: f1 a b - s a - s b delaySY:: a - s a - s a zipWithSY :: f2 a b c- s a - s b - s c The goal of this class is to extend the name of the following functions (which BTW are already

[Haskell-cafe] Even better Eratosthenes sieve and lucky numbers

2007-02-12 Thread oleg
We further simplify the previously posted genuine sieve algorithm and generalize it to the finding of lucky numbers. We observe that we only need to store marks _signifying_ the integers, but never the integers themselves. Thus we arrive at the algorithm that is distinguished from all

[Haskell-cafe] Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-11 Thread oleg
It has been already remarked that any algorithm of finding prime numbers that uses division or `mod` operations cannot be called (Eratosthenes) sieve. The insight of Eratosthenes is finding primes without resorting to division or multiplication. In his time, doing either of those operations was

[Haskell-cafe] Are GADTs expressive? Simple proof-carrying code in Haskell98

2007-01-13 Thread oleg
that is convertible to typeclasses in the straightforward way, see for example, http://pobox.com/~oleg/ftp/Haskell/GADT-interpreter.hs Inn this particular example, GADT do not bring any power. Incidentally, the typeclass encoding has an advantage: If the submitted proof is invalid, the error

[Haskell-cafe] MapTuple is possible and easy

2007-01-11 Thread oleg
Marco Tu'lio Gontijo e Silva wrote: is there a way to defined something as a map to use in tuples? Yes, it is: and it is quite easy and straightforward. Udo Stenzel since c would be a variable that ranges over type classes, and that doesn't exist. Of course it does: please see below (as

[Haskell-cafe] restricted existential datatypes

2007-01-11 Thread oleg
Misha Aizatulin wrote I am using existential boxes like data Box cxt = forall a . Sat (cxt a) = Box a here Sat is taken from [1]: class Sat a where dict :: a The result is a box type which can have variable context imposed on its contents. What I noticed is that sometimes I want to

<    1   2   3   4   5   >