[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

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

2007-01-13 Thread oleg
bring. The shown GADT encoding seems to be of the kind 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

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

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

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

2007-02-21 Thread oleg
On 2/21/07, Alfonso Acosta 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 type closures http://www.has

[Haskell-cafe] exists . a psuedo-standard non-empty list module

2007-02-21 Thread oleg
Nicolas Frisby wrote: > Some of the code from the previous wiki link, type-level decimal > numbers I would rather advice against type-level decimal numbers, if we are looking at a lightweight solution. The [complete] code at http://www.haskell.org/haskellwiki/Non-empty_list is Haskell98!

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

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

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

2007-02-26 Thread oleg
endArbitrary a b c they are indeed the same: hence the typechecker 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

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

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

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

2007-02-27 Thread oleg
just 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-

[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: Takusen and strictness, and perils of getContents

2007-03-06 Thread oleg
Simon Marlow wrote: > Anyway, I just wanted to point out that nowadays we have the option of > using imprecise exceptions to report errors in lazy I/O. Is this really a solution? Currently, getContents reports no errors but does perfect error recovery: the result of the computation prior to the e

[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

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 th

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

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

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

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

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

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

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

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

2007-04-16 Thread oleg
Neil Mitchell wrote: > I'm looking for a type class which checks whether two types are the > same or not. This problem is more complex than appears. It has been solved, however. IncoherentInstances are not required, as IncoherentInstances are generally unsafe. For the full discussion of various

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

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

2007-04-18 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

[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 think this is a hard > constraint in Haskell that prevents this level of generality in the > spec

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

[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

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

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

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 su

[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] writing a function to make a correspondance between type-level integers and value-level integers

2013-06-17 Thread oleg
I'm late to this discussion and must have missed the motivation for it. Specifically, how is your goal, vector/tensor operations that are statically assured well-dimensioned differs from general well-dimensioned linear algebra, for which several solutions have been already offered. For example, th

[Haskell-cafe] writing a function to make a correspondance between type-level integers and value-level integers

2013-06-24 Thread oleg
Well, I guess you might be interested in geometric algebra then http://dl.acm.org/citation.cfm?id=1173728 because Geometric Algebra is a quite more principled way of doing component-free calculations. See also the web page of the author http://staff.science.uva.nl/~fontijne/ Geige

[Haskell-cafe] Geometric Algebra [Was: writing a function to make a correspondance between type-level integers and value-level integers]

2013-06-25 Thread oleg
> It seems very interesting, but I have not currently the time to make a > detailed comparison with vector/tensor algebra. Moreover I have not I would suggest the freely available Oersted Medal Lecture 2002 by David Hestenes http://geocalc.clas.asu.edu/pdf/OerstedMedalLe

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-30 Thread oleg
TP wrote: > pr :: Name -> ExpQ > pr n = [| putStrLn $ (nameBase n) ++ " = " ++ show $(varE n) |] The example is indeed problematic. Let's consider a simpler one: > foo :: Int -> ExpQ > foo n = [|n + 1|] The function f, when applied to an Int (some bit pattern in a machine register), produces _c

[Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg
Andreas wrote: > The greater evil is that Haskell does not have a non-recursive let. > This is source of many non-termination bugs, including this one here. > let should be non-recursive by default, and for recursion we could have > the good old "let rec". Hear, hear! In OCaml, I can (and often

[Haskell-cafe] Proposal: Non-recursive let

2013-07-10 Thread oleg
Jon Fairbairn wrote: > It just changes forgetting to use different variable names because of > recursion (which is currently uniform throughout the language) to > forgetting to use non recursive let instead of let. Let me bring to the record the message I just wrote on Haskell-cafe http:/

[Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg
> If you would like to write > > let (x,s) = foo 1 [] in > let (y,s) = bar x s in > let (z,s) = baz x y s in > > instead, use a state monad. Incidentally I did write almost exactly this code once. Ironically, it was meant as a lead-on to the State monad. But there have been other ca

Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg
Alberto G. Corona wrote: > I think that a non-non recursive let could be not compatible with the pure > nature of Haskell. I have seen this sentiment before. It is quite a mis-understanding. In fact, the opposite is true. One may say that Haskell is not quite pure _because_ it has recursive let.

Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg
I'd like to emphasize that there is a precedent to non-recursive let in the world of (relatively pure) lazy functional programming. The programming language Clean has such non-recursive let and uses it and the shadowing extensively. They consider shadowing a virtue, for uniquely typed data. Richa

[Haskell-cafe] Expression problem in the database?

2013-07-23 Thread oleg
Here is one possible approach. First, convert the propositional formula into the conjunctive normal form (disjunctive will work just as well). Recall, the conjunctive normal form (CNF) is type CNF = [Clause] type Clause = [Literal] data Literal = Pos PropLetter | Neg PropLetter type PropL

Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-24 Thread oleg
ivan.chollet wrote: > let's consider the following: > > let fd = Unix.open ... > let fd = Unix.open ... > > At this point one file descriptor cannot be closed. Static analysis will > have trouble catching these bugs, so do humans. Both sentences express false propositions. The given code, if Has

[Haskell-cafe] Proposal: Non-recursive let

2013-07-25 Thread oleg
Here is a snippet from a real code that could benefit from non-recursive let. The example is notable because it incrementally constructs not one but two structures (both maps), ast and headers. The maps are constructed in a bit interleaved fashion, and stuffing them into the same State would be un

Re: [Haskell-cafe] Yet Another Forkable Class

2013-08-21 Thread oleg
Perhaps effect libraries (there are several to choose from) could be a better answer to Fork effects than monad transformers. One lesson from the recent research in effects is that we should start thinking what effect we want to achieve rather than which monad transformer to use. Using ReaderT or

Re: [Haskell-cafe] Yet Another Forkable Class

2013-08-23 Thread oleg
I must stress that OpenUnion1.hs described (briefly) in the paper is only one implementation of open unions, out of many possible. For example, I have two more implementations. A year-old version of the code implemented open unions *WITHOUT* overlapping instances or Typeable. http://okmij.

Re: [Haskell-cafe] stream interface vs string interface: references

2013-09-03 Thread oleg
> For lazy I/O, using shows in Haskell is a good analogue of using > #printOn: in Smalltalk. The basic form is "include this as PART of > a stream", with "convert this to a whole string" as a derived form. > > What the equivalent of this would be for Iteratees I don't yet > understand. Why not t

Re: [Haskell-cafe] reifying typeclasses

2013-09-15 Thread oleg
Evan Laforge wrote: > I have a typeclass which is instantiated across a closed set of 3 > types. It has an ad-hoc set of methods, and I'm not too happy with > them because being a typeclass forces them to all be defined in one > place, breaking modularity. A sum type, of course, wouldn't have th

Re: [Haskell-cafe] reifying typeclasses

2013-09-15 Thread oleg
[I too had the problem sending this e-mail to Haskell list. I got a reply saying the message awaits moderator approval] Evan Laforge wrote: > I have a typeclass which is instantiated across a closed set of 3 > types. It has an ad-hoc set of methods, and I'm not too happy with > them because bein

Re: [Haskell-cafe] reifying typeclasses

2013-09-17 Thread oleg
> I've been toying with using Data Types a la Carte to get type > representations, a `Typeable` class and dynamic types parameterized by a > possibly open universe: If the universe is potentially open, and if we don't care about exhaustive pattern-matching check (which is one of the principal ben

[Haskell-cafe] RankNTypes + ConstraintKinds to use Either as a "union"

2013-10-09 Thread oleg
Thiago Negri wrote: > Why type inference can't resolve this code? > {-# LANGUAGE RankNTypes, ConstraintKinds #-} > > bar :: (Num a, Num b) => (forall c. Num c => c -> c) ->Either a b ->Either a b > bar f (Left a) = Left (f a) > bar f (Right b) = Right (f b) > > bar' = bar (+ 2) -- This compiles o

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

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

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

2008-03-12 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] 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" > re

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

2008-05-13 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 obvio

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

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

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

[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] 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 http://okmij.org/ftp/Computation/tagless-typed.

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

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

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

2009-04-02 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 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

Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-04 Thread oleg
One should keep in mind the distinction between schematic variables (which participate in unification) and universally quantified variables. Let's look at the forall-elimination rule G |- e : forall a. A E G |- e : A[a := t] If the term e has the typ

[Haskell-cafe] Combining Regions and Iteratees

2012-01-21 Thread oleg
Regions is an automatic resource management technique that statically ensures that all allocated resources are freed and a freed resource cannot be used. Regions also promote efficiency by helping to structure the computation so that resources will be freed soon, and en masse. Therefore, regions a

Re: [Haskell-cafe] Is ListT a valid MonadPlus?

2012-02-09 Thread oleg
First of all, ListT is not a monad transformer, since it breaks the law of associativity of bind: *Control.Monad.List> let one = (lift $ putStrLn "1") :: ListT IO () *Control.Monad.List> let two = (lift $ putStrLn "2") :: ListT IO () *Control.Monad.List> let choice = return 1 `mplus` return 2 ::

[Haskell-cafe] Clarifying a mis-understanding about regions (and iteratees)

2012-02-22 Thread oleg
hat file A is closed before file B is opened? To which the user tibbe replied > You can typically explicitly close the files as well. and the user dobryak commented > Regions that Oleg refers to started out with region-based memory allocation, > which is effectively a stack allocation strate

Re: [Haskell-cafe] Adding type annotations to an AST?

2012-03-05 Thread oleg
> How do I add type annotations to interior locations in an abstract > syntax tree? > i.e. the type it [algorithm] infers is the type of the whole > program, I would also like the types of any internal let-rec > definitions so I can label my AST. I had exactly the same problem: type reconstr

Re: [Haskell-cafe] Are there arithmetic composition of functions?

2012-03-21 Thread oleg
> At present we can easily express different flavors of conjunction, but > expressing disjunction is hard. Disjunction is not particularly difficult. See, for example, http://okmij.org/ftp/Haskell/TTypeable/TTypeable.hs and search for ORELSE. The code demonstrates higher-order type-lev

Re: [Haskell-cafe] Fail-back monad

2012-03-29 Thread oleg
Alberto G. Corona wrote about a monad to set a checkpoint and be able to repeatedly go to that checkpoint and re-execute the computations following the checkpoint. http://haskell-web.blogspot.com.es/2012/03/failback-monad.html The typical example is as follows. > test= runBackT $ do >l

Re: [Haskell-cafe] Fail-back monad

2012-04-05 Thread oleg
> I thoutgh on the use or ErrorT or something similar but the fact is > that i need many bacPoints, not just one. That is, The user can go > many pages back in the navigation pressing many times te back > buttton. The approach in the previous message extends to an arbitrary, statically unknown nu

Re: [Haskell-cafe] heterogeneous environment

2012-05-02 Thread oleg
Ben wrote: > - use Data.Unique to identify Refs, and use existential quantification > or Data.Dynamic to create a heterogenous Map from uid to log. for > example, to represent a log of compare-and-swaps we might do something > like > data Ref a = Ref (IORef a) Unique > data OpaqueCAS = forall a

Re: [Haskell-cafe] [Q] multiparam class undecidable types

2012-05-08 Thread oleg
> | instance (Table a c, Show c) => Show a where > I would have thought that there is on overlap: the instance in my code > above defines how to show a table if the cell is showable; No, the instance defines how to show values of any type; that type must be an instance of Table. There is no `if'

Re: [Haskell-cafe] Un-memoization

2012-05-08 Thread oleg
Victor Miller wrote: > I was writing a Haskell program which builds a large labeled binary tree > and then does some processing of it, which is fold-like. In the actual > application that I have in mind the tree will be *huge*. If the whole tree > is kept in memory it would probably take up 100'

Re: [Haskell-cafe] [Q] multiparam class undecidable types

2012-05-10 Thread oleg
> i think what i will do is to instantiate all table types individually: > | instance Show c => Show (SimpleTable c) where > | showsPrec p t = showParen (p > 10) $ showString "FastTable " . > | shows (toLists t) I was going to propose this solution, as we

[Haskell-cafe] Using promoted lists

2012-06-07 Thread oleg
Yves Pare`s wrote: > So I'm trying to make a type level function to test if a type list contains > a type. Unless I'm wrong, that calls to the use of a type family. More crucially, list membership also calls for an equality predicate. Recall, List.elem has the Eq constraint; so the type-level mem

[Haskell-cafe] Long-running request/response protocol server ...

2012-06-28 Thread oleg
Nicolas Trangez wrote > The protocol I'd like to implement is different: it's long-running using > repeated requests & responses on a single client connection. Basically, > a client connects and sends some data to the server (where the length of > this data is encoded in the header). Now the serv

Re: [Haskell-cafe] translation between two flavors of lexically-scoped type variables

2012-07-06 Thread oleg
Kangyuan Niu wrote: > Aren't both Haskell and SML translatable into System F, from which > type-lambda is directly taken? The fact that both Haskell and SML are translatable to System F does not imply that Haskell and SML are just as expressive as System F. Although SML (and now OCaml) does have

Re: [Haskell-cafe] translation between two flavors of lexically-scoped type variables

2012-07-07 Thread oleg
> Do you know why they switched over in GHC 6.6? If I were to speculate, I'd say it is related to GADTs. Before GADTs, we can keep conflating quantified type variables with schematic type variables. GADTs seem to force us to make the distinction. Consider this code: data G a where GI :: Int

Re: [Haskell-cafe] Interest in typed relational algebra library?

2012-07-10 Thread oleg
> And yes to first order predicate calculus too! Just two weeks ago Chung-chieh Shan and I were explaining at NASSLLI the embedding in Haskell of the higher-order predicate logic with two base types (so-called Ty2). The embedding supports type-safe simplification of formulas (which was really nee

[Haskell-cafe] Monads with "The" contexts?

2012-07-12 Thread oleg
Tillmann Rendel has correctly noted that the source of the problem is the correlation among the random variables. Specifically, our measurement of Sun's mass and of Mars mass used the same rather than independently drawn samples of the Earth mass. Sharing (which supports what Functional-Logic prog

Re: [Haskell-cafe] Monads with "The" contexts?

2012-07-14 Thread oleg
The bad news is that indeed you don't seem to be able to do what you want. The good news: yes, you can. The enclosed code does exactly what you wanted: > sunPerMars :: NonDet Double > sunPerMars = (/) <$> sunMass <*> marsMass > > sunPerMars_run = runShare sunPerMars > sunPerMars_run_len = length

Re: [Haskell-cafe] Haskell's type inference considered harmful

2012-07-17 Thread oleg
>1. Haskell's type inference is NON-COMPOSITIONAL! Yes, it is -- and there are many examples of it. Here is an example which has nothing to do with MonomorphismRestriction or numeric literals {-# LANGUAGE ExtendedDefaultRules #-} class C a where m :: a -> Int instance C () where m

Re: [Haskell-cafe] Monads with "The" contexts?

2012-07-19 Thread oleg
> http://en.pk.paraiso-lang.org/Haskell/Monad-Gaussian > What do you think? Will this be a good approach or bad? I don't think it is a Monad (or even restricted monad, see below). Suppose G a is a `Gaussian' monad and n :: G Double is a random number with the Gaussian (Normal distribution). Then

[Haskell-cafe] Probabilistic programming [Was: Monads with "The" contexts?]

2012-07-19 Thread oleg
> > Exercise: how does the approach in the code relate to the approaches > > to sharing explained in > > http://okmij.org/ftp/tagless-final/sharing/sharing.html > > > Chapter 3 introduces an implicit impure counter, and Chapter 4 uses a > database that is passed around. > let_ in Chapter

Re: [Haskell-cafe] Haskell's type inference considered harmful

2012-07-21 Thread oleg
> However, if your are using ExtendedDefaultRules then you are likely to > know you are leaving the clean sound world of type inference. First of all, ExtendedDefaultRules is enabled by default in GHCi. Second, my example will work without ExtendedDefaultRules, in pure Haskell98. It is even shor

[Haskell-cafe] CRIP: the Curiously Reoccuring Instance Pattern

2012-07-31 Thread oleg
Ryan Ingram wrote: > I've been seeing this pattern in a surprising number of instance > definitions lately: > > instance (a ~ ar, b ~ br) => Mcomp a ar b br [1] > instance (b ~ c, CanFilterFunc b a) => CanFilter (b -> c) a [2] And here are a few more earlier instances of the same occurrence:

Re: [Haskell-cafe] CRIP: the Curiously Reoccuring Instance Pattern

2012-08-01 Thread oleg
> did you see this, and the discussion around that time? > http://www.haskell.org/pipermail/haskell-prime/2012-May/003688.html > > I implemented hDeleteMany without FunDeps -- and it works in Hugs (using > TypeCast -- but looks prettier in GHC with equality constraints). I'm afraid I didn't see

<    1   2   3   4   5   >