[Haskell] GADT and constraints [Was: Rebindable syntax for monads and arrows]

2005-01-10 Thread oleg
Simon Peyton-Jones wrote: |[ data MyVec a where |[ MkMyVec :: (Foo a) => a -> MyVec a > > f x = case x of > MkMyVec x -> > > constraints are always solved *lazily* when inferring, so we'd infer > f :: Foo [a] => MyVec a -> ... > even without any over

[Haskell] Re: A puzzle and an annoying feature

2004-11-24 Thread oleg
Andrew Bromage wrote: > module FD where > > class C from to | from -> to where > g :: from -> to > h :: to -> from > > instance C Char Bool where > g c = c == 'T' > h b = if b then 'T' else 'F' > > --f :: (C Char a) => Char -> a > f c = g c Indeed, functional dependencies are

[Haskell] Typeful symbolic differentiation of compiled functions

2004-11-24 Thread oleg
Jacques Carette wrote on LtU on Wed, 11/24/2004 ] One quick (cryptic) example: the same difficulties in being able to ] express partial evaluation in a typed setting occurs in a CAS ] [computer algebra system]. Of course I mean to have a partial ] evaluator written in a language X for language X,

[Haskell] Closed Projections on HLists?

2004-11-17 Thread oleg
Jared Warren wrote: > I'm doing some work with heterogeneous sets as provided by the HList > library . My code uses > projections of sets internally and I keep running into the open-world > assumption when I ask the type checker to infer the result of > projec

[Haskell] Re: Parameterized Show

2004-11-15 Thread oleg
George Russel wrote: > Graham Klyne wrote (snipped): > > I like the principle of parameterizing Show to allow for different > > encoding environments... > > I like the idea too, not just for Show but for any instances. It seems to > me that in general you should be able to combine the convenien

[Haskell] How to close a type class

2004-11-11 Thread oleg
It is well known that type classes in Haskell are open. A user may at any time extend a visible type class by providing a new instance. There are situations where such an extensibility is undesirable. We may want to prevent the user from adding an instance to our class for some specific type -- or

[Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread oleg
estions do arise in Scheme -- where the agreement seems to be to have two kinds of imports: regular import and import for-syntax. [regarding partial signatures] > Ah! I had forgotten about that. See also: > > http://www.mail-archive.com/[EMAIL PROTECTED]/msg05186.html Incidently, some

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread oleg
Jo'n Fairbairn wrote: > The idea is simply that we should provide a mechanism of > saying to a compiler "this file (of data) is a module that > exports only the variable v". ... > So we tell the compilation system that file > /somewhere/contains-v contains the value of the variable > v::String, an

Re: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-10 Thread oleg
Dominic Steinitz wrote: > Did you get the first solution to work? When I tried it with hugs -98 I got Yes, in the process discovering some interesting behavior of Hugs. Here's the complete code that works with Hugs > module Foo where > > class Bits a > > instance (Ord a, Bits a, Bounded a, Inte

[Haskell] Re: threading mutable state through callbacks

2004-10-07 Thread oleg
Jules Bean wrote: > Unfortunately, it's not going to work. It's not going to work because > some of the procedures take callbacks, and the callbacks are values of > type IO (). I can see two solutions to this: > > a) revert to using an IORef, and use lexical scoping to define my > callbacks in a l

[Haskell] GHC / Hugs Disagree on Constraints

2004-10-04 Thread oleg
> instance (Ord a, Bits a, Bounded a, Integral a, LargeWord a, > Bits b, Bounded b, Integral b, LargeWord b) => > Bounded (LargeKey a b) where >minBound = 0 >maxBound = > fromIntegral $ > (1 + fromIntegral (maxBound::b))* > (1

[Haskell] Applicative translucent functors in Haskell

2004-08-27 Thread oleg
ML is known for its sophisticated, higher-order module system, which is formalized in Dreyer-Crary-Harper language. A few months ago Ken Shan showed a complete translation of that language into System Fw: http://www.eecs.harvard.edu/~ccshan/xlate/ Ken Shan has concluded that languages ba

[Haskell] Re: Dependent Types in Haskell

2004-08-14 Thread oleg
Martin Sulzmann stated the goal of the append exercise as follows: ] Each list carries now some information about its length. ] The type annotation states that the sum of the output list ] is the sum of the two input lists. I'd like to give a Haskell implementation of such an append function, wh

[Haskell] Keyword arguments

2004-08-13 Thread oleg
We show the Haskell implementation of keyword arguments, which goes well beyond records (e.g., in permitting the re-use of labels). Keyword arguments indeed look just like regular, positional arguments. However, keyword arguments may appear in any order. Furthermore, one may associate defaults wit

Re: [Haskell] Eliminating Array Bound Checking through Non-dependent types

2004-08-08 Thread oleg
Hello! Bjorn Lisper wrote: > What is the relation to the sized types by Lars Pareto and John Hughes? It is orthogonal and complementary, as the message in response to Conor T. McBride indicated. > What is the relation to classical range analyses for (e.g.) array index > expressions, which have

Re: [Haskell] Eliminating Array Bound Checking through Non-dependent types

2004-08-06 Thread oleg
a proof; shouting didn't help. Incidentally, the paper is being considered for JFP, I guess. I don't know if the text could be made available. I still can post the link to the code: http://pobox.com/~oleg/ftp/Haskell/number-param-vector-code.tar.gz I should emphasize that all prope

[Haskell] Eliminating Array Bound Checking through Non-dependent types

2004-08-05 Thread oleg
There is a view that in order to gain static assurances such as an array index being always in range or tail being applied to a non-empty list, we must give up on something significant: on data structures such as arrays (to be replaced with nested tuples), on general recursion, on annotation-free

[Haskell] Re: type class does not compile

2004-07-12 Thread oleg
Ben Yu wrote: > class Rule r u u' m where > apply :: r -> u -> m u' > > data And = And > > data Bin a b o = Bin a b o > > instance (Monad m, Rule r1 u u' m, Rule r2 u' u'' m) => > Rule (Bin r1 r2 And) u u'' m where > apply (Bin r1 r2 _) u = apply r1 u >>= apply r2 > > Ghc complains

[Haskell] Exceptions in types and exception-free programming

2004-06-24 Thread oleg
S. Alexander Jacobson wrote: > Also, is there a way to get the typesystem to > tell you which functions may fail i.e. which > functions have failMsg as an implicit parameter? Generally speaking, that is not that easy. If we have a functional composition (foo . bar), we wish its

[Haskell] Re: closure of coercions with classes

2004-06-18 Thread oleg
> The guts of the question is: can one use the class system to code up > the reflexive, transitive closure Computing the transitive closure of types is possible: http://www.haskell.org/pipermail/haskell-cafe/2003-October/005249.html http://www.haskell.org/pipermail/haskell-cafe/2003-November/0054

[Haskell] The two-class trick

2004-06-15 Thread oleg
The two-class trick helps us indirectly write desirable multi-parameter classes with functional dependencies or overlapping. The example below happens to have both. The example illustrates that an attempt to write desired instances directly runs into problems of bad overlapping or violations of fu

[Haskell] Re: how to write a list builder? fixpoint?

2004-06-08 Thread oleg
Ben Yu wrote: > I'm new to haskell, new to this group, don't even know what this > "cafe" refers to. Is there a special place for discussing further > details? Yes, http://haskell.org/mailman/listinfo/haskell-cafe >Similarly, a builder can be built for binary functions like addToFM. Here's a b

[Haskell] Re: how to write a list builder? fixpoint?

2004-06-02 Thread oleg
I'm sorry I couldn't resist another example -- which requires fewer signatures. It also illustrates storing build in data structures. In the example below (which works with the code posted earlier) build is used to build itself. It really has quite a few faces... data W = W (forall r a. (BuildLis

[Haskell] Re: how to write a list builder? fixpoint?

2004-06-02 Thread oleg
> Another question about overloading with type classes. It seems that these > overloaded functions cannot be passed as higher-order function. Is that > true? A higher order function can never be overloaded? > > In an example, how can I pass "build" as a function to another function > that does som

[Haskell] Re: how to write a list builder? fixpoint?

2004-06-01 Thread oleg
> Is it possible to write a function to build a list [a]? > so that I can write [a,b,c,d] as "getBuilt $ build a b c d"? Yes, in the format very close to desired. > {-# OPTIONS -fglasgow-exts #-} > {-# OPTIONS -fallow-undecidable-instances #-} > > module Foo where > > class BuildList a r | r->

Re: [Haskell] a newbie question

2004-04-24 Thread oleg
> I was thinking about creating a generic monad that can persist state change > even when fail is called. The StateT monad will discard the state change so > it makes it hard to add tracing to the program. (at least to me. If there's > any nice way of doing this, please kindly instruct me.) If yo

Re: [Haskell] Correct interpretation of the curry-howard isomorphism

2004-04-23 Thread oleg
> So, either the interpretation of the isomorphism is wrong, or Haskell > type syste m is in fact unsound. Right ? > They cannot be both true! Let us indeed examine what exactly it means for a type system to be sound. The soundness of a type system is usually proved as a theorem of a form:

[Haskell] Re: concurrent haskell, higher-order types and parameterizing by typeclass

2004-04-13 Thread oleg
> data Showable = forall a. Show a => Showable a > > writer :: Chan Showable -> IO () > writer ch = mapM_ (writeChan ch) [Showable 42, Showable pi, Showable > "hello", Showable 'c'] > > printer :: Chan Showable -> IO () > printer ch = getChanContents ch >>= mapM_ (\(Showable a) -> print a) > > How

[Haskell] Overapping instances [Was: What is the best way to write adapters?]

2004-03-12 Thread oleg
Ben Yu wrote: > The instance declaration is like this: > instance FwdSig Native > instance FwdSig Def > instance FwdSig d => Sig d > instance Sig XXX > > Neither Native nor Def are direct instances of Sig. > And this XXX, it is an instance of Sig, not a FwdSig. > > As you can see, there's no real

[Haskell] What is the best way to write adapters?

2004-03-11 Thread oleg
> The code is currently like this: > instance Sig Def where > getName (DefClass c) = getName c > getName(DefProtocol p) getName p > getName(DefSignature s) = getName s > getParents(DefClass c) = getParents c > getParents(DefProtocol p) = getParents p > blah blah blah... > > But this see

[Haskell] Re: performance tuning Data.FiniteMap

2004-03-02 Thread oleg
[BTW, should we move to Haskell-Cafe?] > Because updates are not so infrequent that I want to pay the cost of > replicating the entire array every update (or every ten!). I'm > willing to exchange *some* read time for faster update. Also, because > small array copies may be sufficiently faster t

RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-01 Thread oleg
Simon Peyton-Jones wrote: > In Haskell today, you can at least tell what value is bound to each > identifier in the program, *without* first doing type checking. I'm afraid I'm confused. In the following code > data Z > data S a > > class Card c where c2int:: c -> Int > > instance Card Z where

[Haskell] Re: performance tuning Data.FiniteMap

2004-03-01 Thread oleg
Hello! If indeed the read performance is at premium and updates are infrequent, by bother with ternary etc. trees -- why not to use just a single, one-level array. Given a reasonable hash function, the retrieval performance is O(1). And still, no IO/ST are necessary. {-# OPTIONS -fglasg

Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread oleg
Hello! > So, how can you come up with a type class which provides a polymorphic > 'add' function, considering you don't even know how many parameters > each data type's individual add function uses? Very easily: every Haskell function takes only one argument. Always. Ever. > For example, say I'

[Haskell] Re: Functional dependencies interfere with generalization

2004-01-28 Thread oleg
I'm sorry to open an old wound. I've just had an insight for a clarification. On Nov 26, 2003 Ken Shan wrote: > Consider the following code, which uses type classes with functional > dependencies: > > {-# OPTIONS -fglasgow-exts #-} > module Foo where > class R a b | a -> b where r ::

Re: GHC, functional dependency, rank-2 type

2004-01-13 Thread oleg
John Tromp wrote: > >>instance (Bar a) => Foo a > I have tried to write code myself like in the last line, > stating that any instance of one class should also be > an instance of another class. But Hugs would complain about > it. You're right. Hugs needs to be told that the code is in an extend

GHC, functional dependency, rank-2 type

2004-01-12 Thread oleg
There appears to be a problem with GHC's handling of multi-parameter constraints with functional dependencies in the context of rank-2 types. The problem is not present in Hugs. Let us first consider a simple example: > module Test where > class Foo a > > class Bar a > > data Obj = Obj > > insta

mfix as an effect

2004-01-11 Thread oleg
Can mfix be considered as "just a fix point combinator", without any trace of effect? The recent discussion about continuations and implementations of Scheme in Haskell highlighted that question. The point of the discussion is the difference between letrec implemented using the fixpoint combinato

Re: getting the path to the executing program

2004-01-09 Thread oleg
Hal Daume wrote: > is there a function, related to getProgName, which returns the (absolute) > path to the current program? > basically, i want to be able to read a file which i know will be in the > same directory as the current program, but not necessarily in the same > directory that we're run

Re: lifting functions to tuples?

2003-11-19 Thread oleg
The problem: liftTup f (a, b) = (f a, f b) of the signature liftTup:: ?? -> (a,b) -> (c,d) Again, it is possible to write this in Haskell with common extensions > {-# OPTIONS -fglasgow-exts #-} > import Data.Dynamic > import Data.Maybe > liftp f (a,b) = ((fromJust . fromDynamic . f .

Re: lifting functions to tuples?

2003-11-18 Thread oleg
Abraham Egnor wrote: > The classic way to write a lift function for tuples is, of course: > liftTup f (a, b) = (f a, f b) > which has a type of (a -> b) -> (a, a) -> (b, b). I've been wondering if > it would be possible to write a function that doesn't require the types in > the tuple to be th

Re: Enum on Float/Double

2003-10-22 Thread oleg
> I found a case where I really need: > f :: Float -> Float > where > f x is the least y such that x < y This seems to be the problem of finding the unnormalized epsilon: the smallest positive number one can meaningfully add to the given number x. If that x is 1.0, we're talking about the eps

Re: type class problem

2003-09-30 Thread oleg
Dean Herington wrote: > Can someone explain why the following doesn't work? > {-# OPTIONS -fglasgow-exts #-} > class R r where > rId :: r -> String > class (R r) => RT r t where > rtId :: r -> t -> String > data RPair r1 r2 = RPair r1 r2 > instance (R r1, R r2) => R (RPair r1 r2) where >

From enumerators to cursors: turning the left fold inside out

2003-09-23 Thread oleg
'0' reading from stream2. Got '0' Reading 2 chars from one stream reading from stream1. Got '1' reading from stream1. Got '2' Read: "01" Reading 3 chars from the second stream reading from stream2. Got '1' reading from stream2

Re: Polymorphic Recursion / Rank-2 Confusion

2003-09-22 Thread oleg
the time or using lists and losing the > capability of ensuring I am manipulating lists of the same length. Perhaps you might find the following http://pobox.com/~oleg/ftp/Haskell/number-parameterized-types.html relevant to your task. The page demonstrates bitvectors of a statically-ch

Re: Circular Instance declarations

2003-09-07 Thread oleg
Ashley Yakeley wrote: > Would it be reasonable for the compiler to check back through the > stack and allow the circularity? It will just create an ordinary > recursive function. The following works. Flags: -fglasgow-exts -fallow-undecidable-instances data D r = ZeroD | SuccD (r (D r)) in

Re: proving the monad laws

2003-09-04 Thread oleg
Hello! > Would it be possible to write a piece of Haskell code which checks > the monadic laws automatically by simulating evaluation in this way? To some extent, yes. The proof in the previous message was based on normalization, with respect to associative laws and some betas. So we can take

Re: proving the monad laws

2003-09-02 Thread oleg
Steffen Mazanek posed a problem: given the monad: > data Error a = Error String | Ok a > data TI a = TI (Subst -> Int -> Error (Subst, Int, a)) > instance Monad TI where > return x = TI (\s n -> Ok (s,n,x)) > TI f >>= g = TI (\s n -> case f s n of >Ok (s',m,x) -> l

RE: Type class problem

2003-08-27 Thread oleg
Simon Peyton-Jones wrote: > > instance (Show (f (Mu f))) => Show (Mu f) where > >show (In x) = show x > > > > instance Show (N (Mu N)) where > >show Z = "Z" > >show (S k) = "S "++show k > But again, it's fragile isn't it? You are dicing with non-termination > if you have instance dec

AW: container for different types, avoiding boiler plate

2003-08-22 Thread oleg
> > There is no need for Maybe. In fact, if you attempt to fetch > > a type that you didn't put into the attrs, you get a _compile-time_ > > error. > But I'm not sure if it's suitable for what I'm doing, as the attributes > get inserted at run time, and not all of them appear everywhere. So > Ma

Re: container for different types, avoiding boiler plate

2003-08-21 Thread oleg
You might also wish to look at the typed heaps, which have been discussed here on many occasions. Given the constant piece of code in the appendix (which does *not* depend on user types and can be put into a separate, constant module) you can write > data Gender = Masc | Fem | Neutr deriving (S

Re: overlapping instances and functional dependencies

2003-08-20 Thread oleg
Wolfgang Jeltsch has observed: > I have this code: > class C a b c | a b -> c where > f :: a -> b -> c > > instance C a b c => C a (x,y,b) c where > f a (_,_,b) = f a b > > instance C a (a,c,b) c where > f _ (_,c,_) = c > ghci -fglasgow-exts -fallow-overlapping-

Re: Type class problem

2003-08-17 Thread oleg
> I defined type recursion and naturals as > >newtype Mu f = In {unIn :: f (Mu f)} > >data N f = S f | Z > >type Nat = Mu N > An application of Mu should be showable if the functor maps showable types > to showable types, so the most natural way to define the instance seemed > to be > instance

Re: *safe* coerce: four methods compared

2003-08-05 Thread oleg
This message illustrates how safe casting with multiple universes can be extended to new user-defined, polymorphic datatypes. We show a _portable_ mapping of polymorphic types to integers. Different instances of a polymorphic type map to different integers. Phantom types can be either disregarded

Re: *safe* coerce, for regular and existential types

2003-08-02 Thread oleg
> Does this technique extend to polymophic types? Yes, of course. The type F a b in the earlier message was polymorphic. > Let's say we have the following type: > > data D a = C | D a > Is it possible to index the type D a? I have just lifted the polymorphic Maybe -- which is isomorphic to you

*safe* coerce: four methods compared

2003-08-01 Thread oleg
This is a "Related Work" section of the previous message. We compare three main methods of achieving safe casts. It seems that the method proposed in the earlier message is quite different -- especially in terms of extensibility. In this message, we compare the extensibility of four techniques. St

*safe* coerce, for regular and existential types

2003-07-31 Thread oleg
This message describes functions safeCast and sAFECoerce implemented in Haskell98 with common, pure extensions. The functions can be used to 'escape' from or to existential quantification and to make existentially-quantified datatypes far easier to deal with. Unlike Dynamic, the present approach i

Pure functional TypeRep [Was: Existentials...]

2003-07-29 Thread oleg
This message shows how to map _types_ to integers at compile time -- and then extend this facility to run-time so it can be used with existentially-quantified types. It is statically guaranteed that different types receive different integer labels. Unlike TyCons of Dynamics, our mapping does NOT r

Re: Function composition and currying

2003-07-17 Thread oleg
0 The Web page referenced below shows an advanced application of mcomp, to point-free programming (categorical products). [1] http://pobox.com/~oleg/ftp/Haskell/types.html The following code, excerpted from [1], was used for the above examples. -fglasgow-exts are needed. > class MCompose f

Re: Overlapping instances in existentials

2003-06-20 Thread oleg
Ed Komp replied to Simon Peyton-Jones: > Within the GHC compiler > > can't be instantiated to Double --- but that's tricky to pin down. > this may be tricky to pin down. > But, there is specific information in my example to exclude Double: > I had carefully constructed the type definitions to avo

Re: Typesafe MRef's

2003-06-18 Thread oleg
> So what does the function > insert2 val1 val2 = >let > (m1,k1) = insert empty (Just val1) > (m2,k2) = insert m1 (Just val2) > m3 = update m2 k1 Nothing >in > isJust (lookup m3 k2) > return? It looks to me as if it returns True if val1

Re: Typesafe MRef with a regular monad

2003-06-10 Thread oleg
> update :: (Typable b) => FM k -> Key k a -> b -> (FM ...) I didn't know constraints on values are allowed... Given below is the implementation of the required interface, in Haskell98 module TypedFM where data FM k -- Abstract; finite map indexed bykeys of type k data Ke

Typesafe MRef with a regular monad

2003-06-05 Thread oleg
It seems it is possible to implement polymorphic references using the regular (not IO and not ST) monad and without resorting to any unsafe extension. Furthermore, that monad has a run function, which does not compromise the type safety. When I claimed in the previous message that the polytypic n

Re: Safe and sound STRef

2003-06-04 Thread oleg
> Heaps should be more dynamic than this; the (type of the) *reference* > should encode the type it points to, but the (type of the) *heap* > should not. However, the heap can store polymorphic values. Therefore, we can use a heap to store the polymorphic heap... Your example, slightly re-written

Safe and sound STRef [Was Implementing RefMonads in Haskell without ST,IO]

2003-06-03 Thread oleg
Back in September 2001, Koen Claessen wrote: ] Here is a little experiment I did a while ago. I was trying to isolate ] the capability of the ST monad to deal with different types at the ] same time I conjecture this functionality cannot be implemented ] in Haskell 98, nor in any of the known

Re: Eval in Haskell

2003-06-02 Thread oleg
Tomasz Zielonka wrote: > I don't know how it works in Python, but in perl the code in eval is > executed in current lexical scope. Eval of the kind let x = 1 in eval "x" is plainly an abomination. Such an eval all but precludes compilation because the compiler is not free to alpha-rename

Eval in Haskell

2003-05-31 Thread oleg
Simon Marlow wrote: > The test driver makes use of 'eval'-style scripting, which none of the > existing Haskell systems has. Doesn't the following qualify as eval? A similar code works even in Hugs. > import System (system, ExitCode(ExitSuccess)) > import Posix(executeFile) > > myconfig_file =

Polishing the boilerplate: a dis-unsafely safe cast

2003-03-24 Thread oleg
Hello! The paper http://research.microsoft.com/~simonpj/papers/hmap/ by Ralf Laemmel and Simon Peyton Jones gave a reference implementation of a 'cast' function. Here's another implementation: cast:: (Show a, Read b) => a -> Maybe b cast = read_as . show where read_as s = ca

RE: simulating dynamic dispatch

2003-03-23 Thread oleg
Hal Daume wrote: > -- *Main> test $ MkFoo (0::Int) > -- Just True > -- *Main> test $ MkBar 'a' > -- Just True > i forgot to mention the constraint > that i don't want the user to have to use the MkFoo/MkBar > constructors. if i could use them internally to 'test', that would be > great, bu

Re: simulating dynamic dispatch

2003-03-20 Thread oleg
> i'm hoping to be able to simulate a sort of dynamic dispatch based on > class instances. It seems you want to dispatch based not on a type but on the constraint of a type. You code almost worked. Here's the a bit updated and working version. class Foo a where { foo :: a -> Bool } class Bar a

RE: flock and sockets

2003-03-20 Thread oleg
John Hughes wrote: > I didn't find this when I needed to lock files, so my solution (under > Unix) was to write a little C code and call it via the FFI. I used a > single lock file, since my application was a CGI script which runs fairly > rarely -- there's no need for a finer grain of locking. M

Re: Class or parameterized type?

2003-03-20 Thread oleg
Hello! > I wasn't aware there was a standard design, Edison is a good standard (in particular, Collection.hs, found, for example, in /usr/local/share/hugs/lib/exts/). The following projects have a lot of helpful code: http://sourceforge.net/projects/hbase/ http://sourceforge.net/

Class or parameterized type?

2003-03-18 Thread oleg
Hello! > Example: I wish to define a structured container type, let's call it a > "RatsNest", that is type-variable in two ways: > (a) it is parameterized by a type of some class, let's call it "RatsTail", > such that a RatsNest is a structure of things that have common > properties. Certain

redefining methods in a subCLASS

2003-03-14 Thread Oleg
r a where speak x = "Manager: " ++ (show x) Thanks Oleg ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Random Permutations

2003-03-06 Thread oleg
te general, not restricted to any Haskell > peculiarities. I'm sorry but this algorithm does NOT in general provide the perfect random permutation. Here's an excerpt from http://pobox.com/~oleg/ftp/Haskell/perfect-shuffle.txt that deals extensively with this issue: A com

Re: fundeps for extended Monad definition

2003-03-05 Thread oleg
Ashley Yakeley wrote: > If this were allowed, it would effectively allow type-lambda > class C a b | a -> b > instance C Int Bool > instance C Bool Char > newtype T a = MkT (forall b.(C a b) => b) > helperIn :: (forall b.(C a b) => b) -> T a > helperIn b = MkT b; -- currently won't work > helper

First-class types

2003-03-03 Thread oleg
The following is a more flexible alternative to overloading. We essentially define a function on types and invoke it, seemingly at run time. No Dynamics or unsafe computations are employed. We only need existential types, multi-parameter classes and functional dependencies. The code also shows how

RE: fundeps for extended Monad definition

2003-03-03 Thread oleg
| > The reason, which is thoroughly explained in Simon Peyton-Jones' | > message, is that the given type signature is wrong: it should read | > f1 :: (exists b. (C Int b) => Int -> b) > Can you give an example of its use? Yes, I can. > class (Show a, Show b) => C a b | a -> b where > do

RE: fundeps for extended Monad definition

2003-02-28 Thread oleg
Hello! It seems we can truly implement Monad2 without pushing the envelope too far. The solution and a few tests are given below. In contrast to the previous approach, here we lift the type variables rather than bury them. The principle is to bring the type logic programming at the level

RE: fundeps for extended Monad definition

2003-02-27 Thread oleg
Hello! Simon Peyton-Jones wrote: > class C a b | a -> b where {} > instance C Int Int where {} > f1 :: (forall b. (C Int b) => Int -> b) > f1 x = undefined Indeed, this gives an error message Cannot unify the type-signature variable `b' with the type `Int' Expected type: Int

Re: Q. about XML support

2003-02-21 Thread oleg
example code demonstrates that parse . unparse . parse === parse [1] http://pobox.com/~oleg/ftp/Scheme/SXML.html [2] http://cvs.sf.net/cgi-bin/viewcvs.cgi/ssax/SSAX/examples/daml-parse-unparse.scm (written in Scheme, sorry) ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Pure File Reading (was: Dealing with configuration data)

2002-09-26 Thread oleg
There is another solution to the problem of configurational parameters. The main part of the solution is portable, does not depend on any pragmas, does not use unsafe operations, does not use implicit parameters, and does not require any modifications to the user code. I must warn that it is also

Proper scaling of randoms

2002-05-06 Thread oleg
This message derives an integer interval mapping function that is not only provably within the given range but also "uniform". This is the function to use when mapping random integers from one interval to a smaller one. Problem: given an integer n within [0..maxn], design a scaling function sc(n

Re: Bug in the scaling of randoms ...

2002-05-06 Thread oleg
Dimitre Novatchev wrote on May 4, 2002: > In his excellent book Simon Thompson defines scaling of the elements of > a sequence of random numbers from the interval [0, 65535] to an > interval [s,t] in the following way (top of page 368): > > scaleSequence :: Int -> Int -> [Int] -> [Int] > > scale

ANN: Normal-order evaluation as bottom-up parsing

2002-04-28 Thread oleg
fference from yacc is that the lambda-calculator "reparses" the result after the successful reduce step. The source and the target languages of our "parser" (lambda-calculator) are the same; therefore, the parser can indeed apply itself. The evaluator's source code: h

trying to tie the knot

2002-04-12 Thread oleg
Hello! Hal Daume III wrote: [description of a parsing problem that involves forward references] Forward references is the problem. To properly solve it, you have to find a fixpoint. The best way to avoid hitting the bottom is to make sure that the fixpoint combinator is applied to a function. H

Re: Lambda over types.

2002-04-02 Thread oleg
-evaluator code (with the regression tests) can be found at http://pobox.com/~oleg/ftp/Computation/rewriting-rule-lambda.txt The calculator is implemented in CPS, in some sort of extended lambda calculus. Therefore, the code has three kinds of lambdas: of the source language, of the transfor

Re: Lambda over types.

2002-03-31 Thread oleg
anatoli wrote: > Attached are two interpreters: one for untyped lambda calculus, I'm afraid the attached interpreter can't be an implementation of the lambda calculus. For one thing, it lacks the hygiene of substitutions: Lambda> :t lambdaEval (A (L X (L Y (A X Y))) T) lambdaEval (A (L X

Re: Z_n in Haskell

2002-03-28 Thread oleg
The Z_n problem doesn't seem to be different from the problem of arrays or bitvectors of a statically-checkable size. If you prefer a decimal specification of the modulus, you may find the following articles relevant. Implementation of fixed-precision decimal types: Main> BV D1 0

<    1   2