[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

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

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

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

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.

[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

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

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

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

Re: [Haskell-cafe] rip in the class-abstraction continuum

2013-05-20 Thread oleg
Type classes are the approach to constrain type variables, to bound polymorphism and limit the set of types the variables can be instantiated with. If we have two type variables to constrain, multi-parameter type classes are the natural answer then. Let's take this solution and see where it leads

Re: [Haskell-cafe] A use case for *real* existential types

2013-05-18 Thread oleg
> > I must say though that I'd rather prefer Adres solution because his > > init > > > init :: (forall a. Inotify a -> IO b) -> IO b > > > > ensures that Inotify does not leak, and so can be disposed of at the > > end. So his init enforces the region discipline and could, after a > It's probably

[Haskell-cafe] Stream processing

2013-05-10 Thread oleg
I'm a bit curious > * be reliable in the presence of async exceptions (solved by conduit, > pipes-safe), > > * hold on to resources only as long as necessary (solved by conduit > and to some degree by pipes-safe), Are you aware of http://okmij.org/ftp/Streams.html#regions wh

[Haskell-cafe] A use case for *real* existential types

2013-05-10 Thread oleg
But Haskell (and GHC) have existential types, and your prototype code works with GHC after a couple of trivial changes: > main = do > W nd0 <- init > wd0 <- addWatch nd0 "foo" > wd1 <- addWatch nd0 "bar" > W nd1 <- init > wd3 <- addWatch nd1 "baz" > printInotifyDesc nd0 > printInoti

Re: [Haskell-cafe] Reinventing a solution to configuration problem

2013-05-10 Thread oleg
I guess you might like then http://okmij.org/ftp/Haskell/types.html#Prepose which discusses implicit parameters and their drawbacks (see Sec 6.2). ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Typeclass with an `or' restriction.

2013-05-10 Thread oleg
Mateusz Kowalczyk wrote: > Is there a way however to do something along the lines of: > > class Eq a => Foo a where bar :: a -> a -> Bool bar = (==) > > > > class Num a => Foo a where bar :: a -> a -> Bool bar _ _ = False > This would allow us to make an instance of Num be an instance of Foo > or

Re: [Haskell-cafe] Is it time to start deprecating FunDeps?

2013-05-02 Thread oleg
> In your class Sum example, > > class Sum x y z | x y -> z, x z -> y > > your own solution has a bunch of helper classes First of all, on the top of other issues, I haven't actually shown an implementation in the message on Haskell'. I posed this as a general issue. In special cases lik

Re: [Haskell-cafe] Space leak in hexpat-0.20.3/List-0.5.1

2013-04-30 Thread oleg
Wren Thornton wrote: > So I'm processing a large XML file which is a database of about 170k > entries, each of which is a reasonable enough size on its own, and I only > need streaming access to the database (basically printing out summary data > for each entry). Excellent, sounds like a job for S

[Haskell-cafe] HList with DataKinds [Was: Diving into the records swamp (possible GSoC project)]

2013-04-28 Thread oleg
Aleksandar Dimitrov wrote: > I've been kicking around the idea of re-implementing HList on the basis of the > new DataKinds [1] extension. The current HList already uses DataKinds (and GADTs), to the extent possible with GHC 7.4 (GHC 7.6 supports the kind polymorphism better, but it had a critica

Re: [Haskell-cafe] Set monad

2013-04-12 Thread oleg
> One problem with such monad implementations is efficiency. Let's define > > step :: (MonadPlus m) => Int -> m Int > step i = choose [i, i + 1] > > -- repeated application of step on 0: > stepN :: (Monad m) => Int -> m (S.Set Int) > stepN = runSet . f > where > f

Re: [Haskell-cafe] unsafeInterleaveST (and IO) is really unsafe [was: meaning of "referential transparency"]

2013-04-12 Thread oleg
> Lazy I/O *sounds* safe. > And most of the alternatives (like conduits) hurt my head, > so it is really *really* tempting to stay with lazy I/O and > think I'm doing something safe. Well, conduit was created for the sake of a web framework. I think all web frameworks, in whatever language, are q

[Haskell-cafe] unsafeInterleaveST (and IO) is really unsafe

2013-04-12 Thread oleg
Timon Gehr wrote: > I am not sure that the two statements are equivalent. Above you say that > the context distinguishes x == y from y == x and below you say that it > distinguishes them in one possible run. I guess this is a terminological problem. The phrase `context distinguishes e1 and e2' is

[Haskell-cafe] Set monad

2013-04-11 Thread oleg
The question of Set monad comes up quite regularly, most recently at http://www.ittc.ku.edu/csdlblog/?p=134 Indeed, we cannot make Data.Set.Set to be the instance of Monad type class -- not immediately, that it. That does not mean that there is no Set Monad, a non-determinism monad that r

[Haskell-cafe] unsafeInterleaveST (and IO) is really unsafe [was: meaning of "referential transparency"]

2013-04-10 Thread oleg
One may read this message as proving True === False without resorting to IO. In other words, referential transparency, or the substitution of equals for equals, may fail even in expressions of type Bool. This message is intended as an indirect stab at lazy IO. Unfortunately, Lazy IO and even the

Re: [Haskell-cafe] closed world instances, closed type families

2013-04-02 Thread oleg
Henning Thielemann wrote: > However the interesting part of a complete case analysis on type level > peano numbers was only sketched in section "8.4 Closed type > families". Thus I tried again and finally found a solution that works > with existing GHC extensions: You might like the following mes

Re: [Haskell-cafe] attoparsec and backtracking

2013-03-18 Thread oleg
Wren Thornton wrote: > I had some similar issues recently. The trick is figuring out how to > convince attoparsec to commit to a particular alternative. For example, > consider the grammar: A (B A)* C; where if the B succeeds then we want to > commit to parsing an A (and if it fails then return A'

Re: [Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-13 Thread oleg
Jeremy Shaw wrote: > It would be pretty damn cool if you could create a data type for > generically describing a monadic parser, and then use template haskell > to generate a concrete parser from that data type. That would allow > you to create your specification in a generic way and then target >

[Haskell-cafe] Help to write type-level function

2013-02-27 Thread oleg
Dmitry Kulagin wrote: > I try to implement typed C-like structures in my little dsl. HList essentially had those http://code.haskell.org/HList/ > I was unable to implement required type function: > type family Find (s :: Symbol) (xs :: [(Symbol,Ty)]) :: Ty > Which just finds a type in a

[Haskell-cafe] Thunks and GHC pessimisation

2013-02-26 Thread oleg
Tom Ellis wrote: > To avoid retaining a large lazy data structure in memory it is useful to > hide it behind a function call. Below, "many" is used twice. It is hidden > behind a function call so it can be garbage collected between uses. As you discovered, it is quite challenging to ``go again

[Haskell-cafe] parser combinator for left-recursive grammars

2013-02-20 Thread oleg
It is indeed true that a grammar with left-recursion can be transformed to an equivalent grammar without left recursion -- equivalent in terms of the language recognized -- but _not_ in the parse trees. Linguists in particular care about parses. Therefore, it was linguists who developed the parser

Re: [Haskell-cafe] generalized, tail-recursive left fold that can

2013-02-19 Thread oleg
> > That said, to express foldl via foldr, we need a higher-order > > fold. There are various problems with higher-order folds, related to > > the cost of building closures. The problems are especially severe > > in strict languages or strict contexts. Indeed, > > > > foldl_via_foldr f z l = fol

Re: [Haskell-cafe] generalized, tail-recursive left fold that can finish tne computation prematurely

2013-02-18 Thread oleg
As others have pointed out, _in principle_, foldr is not at all deficient. We can, for example, express foldl via foldr. Moreover, we can express head, tail, take, drop and even zipWith through foldr. That is, the entire list processing library can be written in terms of foldr: http://okm

[Haskell-cafe] why GHC cannot infer type in this case?

2013-02-01 Thread oleg
Dmitry Kulagin wrote: > I try to implement little typed DSL with functions, but there is a problem: > compiler is unable to infer type for my "functions". One way to avoid the problem is to start with the tagless final representation. It imposes fewer requirements on the type system, and is a qu

[Haskell-cafe] resources for learning Hindley-Milner type inference for undergraduate students

2013-01-18 Thread oleg
Petr Pudlak wrote: > could somebody recommend me study materials for learning Hindley-Milner > type inference algorithm I could recommend to undergraduate students? Perhaps you might like a two-lecture course for undergraduates, which uses Haskell throughout http://okmij.org/ftp/Haskell

Re: [Haskell-cafe] How to fold on types?

2012-12-25 Thread oleg
Magiclouds asked how to build values of data types with many components from a list of components. For example, suppose we have data D3 = D3 Int Int Int deriving Show v3 = [1::Int,2,3] How can we build the value D3 1 2 3 using the list v3 as the source for D3's fields? We can't u

Re: [Haskell-cafe] Is it possible to have constant-space JSON decoding?

2012-12-15 Thread oleg
Johan Tibell posed an interesting problem of incremental XML parsing while still detecting and reporting ill-formedness errors. > What you can't have (I think) is a function: > > decode :: FromJSON a => ByteString -> Maybe a > > and constant-memory parsing at the same time. The return type her

[Haskell-cafe] Is it possible to have constant-space JSON decoding?

2012-12-04 Thread oleg
I am doing, for several months, constant-space processing of large XML files using iteratees. The file contains many XML elements (which are a bit complex than a number). An element can be processed independently. After the parser finished with one element, and dumped the related data, the process

Re: [Haskell-cafe] Strange behavior with listArray

2012-11-13 Thread oleg
Alex Stangl wrote: > To make this concrete, here is the real solve function, which computes > a border array (Knuth-Morris-Pratt failure function) for a specified > string, before the broken memoization modification is made: > solve :: String -> String > solve w = let h = length w - 1 >

Re: [Haskell-cafe] Strange behavior with listArray

2012-11-13 Thread oleg
Alex Stangl posed a problem of trying to efficiently memoize a function without causing divergence: > solve = let a :: Array Int Int > a = listArray (0, 3) (0 : f 0) > f k = if k > 0 > then f (a!0) > else 0 : f 1 > in (interca

[Haskell-cafe] forall disappear from type signature

2012-11-03 Thread oleg
Takayuki Muranushi wrote: > Today, I encountered a strange trouble with higher-rank polymorphism. It > was finally solved by nominal typing. Was it a bug in type checker? lack of > power in type inference? > runDB :: Lens NetworkState RIB > runDB = lens (f::NetworkState -> RIB) (\x s -> s { _run

[Haskell-cafe] A clarification about what happens under the hood with foldMap

2012-10-23 Thread oleg
> I was playing with the classic example of a Foldable structure: Trees. > So the code you can find both on Haskell Wiki and LYAH is the following: > > data Tree a = Empty | Node (Tree a) a (Tree a) deriving (Show, Eq) > > instance Foldable Tree where > foldMap f Empty = mempty > foldMap f

[Haskell-cafe] Why Kleisli composition is not in the Monad signature?

2012-10-23 Thread oleg
Andreas Abel wrote: > I tell them that monads are for sequencing effects; and the > sequencing is visible clearly in > >(>>) :: IO a -> IO b -> IO b >(>>=) :: IO a -> (a -> IO b) -> IO b > > but not in > >fmap :: (a -> b) -> IO a -> IO b >join :: IO (IO a) -> IO a Indeed! I'd lik

Re: [Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-23 Thread oleg
> And HList paper left me with two questions. The first one is how much > such an encoding costs both in terms of speed and space. And the > second one is can I conveniently define a Storable instance for > hlists. As I said before, I need all this machinery to parse a great > number of serialized

[Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-18 Thread oleg
First of all, MigMit has probably suggested the parameterization of Like by the constraint, something like the following: data Like ctx = forall a. (ctx a, Typeable a) => Like a instance ALike (Like ALike) where toA (Like x) = toA x instance CLike (Like CLike) where toC (Like x) = toC x

Re: [Haskell-cafe] Type of scramblings

2012-10-12 Thread oleg
Sorry for a late reply. > There are of course more total functions of type `[a]^n -> [a]` than of type > `[a] -> [a]`, in the sense that any term of the latter type can be assigned > the > former type. But, on the other hand, any total function `f :: [a]^n -> [a]` > has an "equivalent" total fun

Re: [Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-25 Thread oleg
> Wouldn't you say then that "Church encoding" is still the more appropriate > reference given that Boehm-Berarducci's algorithm is rarely used? > > When I need to encode pattern matching it's goodbye Church and hello Scott. > Aside from your projects, where else is the B-B procedure used? First

Re: [Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-22 Thread oleg
> do you have any references for the extension of lambda-encoding of > data into dependently typed systems? > Is there a way out of this quagmire? Or are we stuck defining actual > datatypes if we want dependent types? Although not directly answering your question, the following paper Inducti

Re: [Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-20 Thread oleg
Dan Doel wrote: > >> P.S. It is actually possible to write zip function using Boehm-Berarducci > >> encoding: > >> http://okmij.org/ftp/Algorithms.html#zip-folds > > If you do, you might want to consider not using the above method, as I > seem to recall it doing an undesirable amount of ex

[Haskell-cafe] Church vs Boehm-Berarducci encoding of Lists

2012-09-18 Thread oleg
There has been a recent discussion of ``Church encoding'' of lists and the comparison with Scott encoding. I'd like to point out that what is often called Church encoding is actually Boehm-Berarducci encoding. That is, often seen > newtype ChurchList a = > CL { cataCL :: forall r. (a -> r ->

Re: [Haskell-cafe] Transforming a ADT to a GADT

2012-09-15 Thread oleg
Florian Lorenzen wrote: > Now, I'd like to have a function > > typecheck :: Exp -> Maybe (Term t) > > typecheck exp = <...> > that returns the GADT value corresponding to `exp' if `exp' is type > correct. Let us examine that type: typecheck :: forall t. Exp -> Maybe (Term t) Do you rea

[Haskell-cafe] Either Monad and Laziness

2012-09-11 Thread oleg
> I am currently trying to rewrite the Graphics.Pgm library from hackage > to parse the PGM to a lazy array. Laziness and IO really do not mix. > The problem is that even using a lazy array structure, because the > parser returns an Either structure it is only possible to know if the > parser

Re: [Haskell-cafe] type variable in class instance

2012-09-11 Thread oleg
Let me see if I understand. You have events of different sorts: events about players, events about timeouts, events about various messages. Associated with each sort of event is a (potentially open) set of data types: messages can carry payload of various types. A handler specifies behavior of a s

Re: [Haskell-cafe] type variable in class instance

2012-09-10 Thread oleg
Corentin Dupon wrote about essentially the read-show problem: > class (Typeable e) => Event e > > data Player = Player Int deriving (Typeable) > data Message m = Message String deriving (Typeable) > > instance Event Player > > instance (Typeable m) => Event (Message m) > > viewEv

[Haskell-cafe] Rigid skolem type variable escaping scope

2012-08-23 Thread oleg
Matthew Steele asked why foo type-checks and bar doesn't: > class FooClass a where ... > > foo :: (forall a. (FooClass a) => a -> Int) -> Bool > foo fn = ... > > newtype IntFn a = IntFn (a -> Int) > > bar :: (forall a. (FooClass a) => IntFn a) -> Bool > bar (IntFn fn) = foo fn This

[Haskell-cafe] Can pipes solve this problem? How?

2012-08-16 Thread oleg
> Consider code, that takes input from handle until special substring matched: > > > matchInf a res s | a `isPrefixOf` s = reverse res > > matchInf a res (c:cs) = matchInf a (c:res) cs > > hTakeWhileNotFound str hdl = hGetContents hdl >>= return.matchInf str [] > > It is simple,

Re: [Haskell-cafe] Data structure containing elements which are instances of the

2012-08-14 Thread oleg
> It's only a test case. The real thing is for a game and will be > something like: > class EntityT e where >update :: e -> e >render :: e -> IO () >handleEvent :: e -> Event -> e >getBound:: e -> Maybe Bound > data Entity = forall e. (EntityT e) => Entity e > data

[Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-11 Thread oleg
> data A = A deriving Show > data B = B deriving Show > data C = C deriving Show > > data Foo = forall a. Show a => MkFoo a (Int -> Bool) > > instance Show Foo where >show (MkFoo a f) = show a I'd like to point out that the only operation we can do on the first argument of MkFoo is to show to

Re: [Haskell-cafe] Data.Data and OverlappingInstances

2012-08-11 Thread oleg
Timo von Holtz wrote: > class Test a where > foo :: Monad m => m a > > instance Num a => Test a where > foo = return 1 > > instance Test Int where > foo = return 2 > > test constr = fromConstrM foo constr I'm afraid the type checker is right. From the type of fromConstrM fromConstrM :: f

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

2012-08-11 Thread oleg
Anthony Clayden wrote: > So three questions in light of the approach of abandoning FunDeps and > therefore not getting interference with overlapping: > A. Does TTypeable need to be so complicated? > B. Is TTypeable needed at all? > C. Does the 'simplistic' version of type equality testing suffer p

[Haskell-cafe] unix package licensing

2012-08-10 Thread Oleg Sidorkin
System/Posix/DynamicLinker/Module/ByteString.hsc and System/Posix/DynamicLinker/Prim.hsc sources in unix-2.5.1.0 package contains the following reference to GPL-2 c2hs package: -- Derived from GModule.chs by M.Weber & M.Chakravarty which is part of c2hs -- I left the API more or less the same, m

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

2012-08-03 Thread oleg
> I think instead you should have: > - abandoned FunDeps > - embraced Overlapping more! Well, using TypeCast to emulate all FunDeps was demonstrated three years later after HList (or even sooner -- I don't remember when exactly the code was written): http://okmij.org/ftp/Haskell/TypeClass.html#H

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

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

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

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

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

[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

[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

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

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

[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] 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] 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] 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] PEPM12: Second Call For Participation

2011-12-18 Thread oleg
ACM SIGPLAN 2012 Workshop on Partial Evaluation and Program Manipulation http://www.program-transformation.org/PEPM12 January 23-24, 2012. Philadelphia, PA, USA (co-located with POPL'12) Second Call For Participation Program is now available http://www.program-transformation.or

Re: [Haskell-cafe] type level strings?

2011-11-24 Thread oleg
Evan Laforge has defined > data Thing { > thing_id :: ThingId > , thing_stuff :: Stuff > } > newtype ThingId = ThingId String and wishes to statically preclude binary operations with things that have different ThingIds. However, Things and their Ids can be loaded from files and so cannot be

[Haskell-cafe] PEPM 2012: Call for participation

2011-11-22 Thread oleg
ACM SIGPLAN 2012 Workshop on Partial Evaluation and Program Manipulation http://www.program-transformation.org/PEPM12 January 23-24, 2012. Philadelphia, PA, USA (co-located with POPL'12) Call For Participation Online registration is open at https://regmaster3.com/2012conf/POPL12

[Haskell-cafe] Interpreter with Cont

2011-11-22 Thread oleg
I would recommend Ralf Hinze's ICFP00 Pearl Deriving Backtracking Monad Transformers http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.34.4164 He starts with a monad transformer expressed as a free term algebra, and shows step-by-step how to transform it to a more efficient

Re: [Haskell-cafe] Deduce problem.

2011-11-17 Thread oleg
Multi-parameter type classes are more flexible. Here is how you can write your old code: > {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} > > class (ClassA a, ClassB b) => ClassC a b where > from :: a -> [b] > to :: a -> [b] > > data H = H > > class ClassA a where toInt :: a -> I

  1   2   3   4   5   >