[Haskell-cafe] typed final-tagless HOAS interpreter for linear lambda calculus

2013-03-26 Thread jeff p
{- This message presents a typed final-tagless HOAS interpreter for linear lambda calculus (LLC), which makes use of type families and datatype promotion. This code is inspired by Oleg's LLC interpreter using deBruijn indices (http://okmij.org/ftp/tagless-final/course/LinearLC.hs). The basic tech

Re: [Haskell-cafe] CPS Streams

2012-10-10 Thread jeff p
Here is an haste of the original message since it seems like the formatting was lost. http://hpaste.org/76082 sorry about that, Jeff ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Data.Text UTF-8 question

2012-08-30 Thread jeff p
Hello, I have a sample file (attached) which I cannot read into Text: Prelude Control.Applicative> Data.Text.IO.readFile "foo" *** Exception: utf8.txt: hGetContents: invalid argument (invalid byte sequence) Prelude Control.Applicative> Data.Text.Encoding.decodeUtf8 <$> Data.ByteStrin

[Haskell-cafe] Improving HList programming/debugging (longish)

2011-01-11 Thread jeff p
This message shows how to slightly reformulate HLists (and other type-level things) to get better type-checking and more informative error messages. The technique is interesting in that it uses GADTs and functional dependencies and seems to not be implementable with associated type synonyms. It als

Re: [Haskell-cafe] Ocaml for Haskellers tutorial

2010-04-16 Thread jeff p
Hello, One major thing I haven't seen explicitly mentioned yet in this thread is tail recursion. You have to write tail recursively in OCaml (or any strict language) or you will blow the stack. While tail recursion is often wrong (in terms of efficiency) in Haskell, it is always right in OCaml. -

Re: [Haskell-cafe] Request for Comments - hscurrency 0.0.1

2009-08-16 Thread jeff p
Hello, To let the type checker do some work for you, without getting all the way into the territory of the dimensional package, you can use newtypes and a Units class with methods for wrapping and unwrapping Doubles; we use this approach at work and find it strikes a nice balance between useful (s

Re: [Haskell-cafe] Cont, ContT and IO()

2009-07-03 Thread jeff p
Couldn't resist taking the bait... > Well, continuations come from Scheme, and by and large, they are usually > used in languages like Scheme (i.e. PLT web server), or Smalltalk (Seaside > web server), > For a fuller history of continuatios, please see "The Discoveries of Continuations" by John Re

Re: [Haskell-cafe] How to implement type level type equality?

2008-08-25 Thread jeff p
Hello, The HList paper (http://homepages.cwi.nl/~ralf/HList/) presents a reasonable general type level equality (though it requires GHC). The paper also describes some other implementations including the interpretation of types as type-level nats. -Jeff On Mon, Aug 25, 2008 at 8:11 PM, Marc We

Re: [Haskell-cafe] Re: Haskell Propeganda

2008-08-24 Thread jeff p
Hello, > Manual Typeable deriving should probably be disabled :-) > There are legitimate reasons to define your own Typeable instances. Since Typeable already contains all the machinery you need to type a standard functional language, it is nice to just add Typeable instances when defining your ow

Re: [Haskell-cafe] Possible to automatically determine typeclass membership?

2008-03-30 Thread jeff p
Hello, > Is it possible in Haskell + GHC extensions to use reflection > techniques to determine typeclass membership? I'm thinking of things > like the following: > I think the short answer is not in general; i.e. I don't think there is any way to access the members of an arbitrary typeclass (b

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

2008-03-12 Thread jeff p
Hello, Data.Typeable gives you most of what you want except for access to function bodies. -Jeff On Tue, Mar 11, 2008 at 6:17 AM, Martin Hofmann <[EMAIL PROTECTED]> wrote: > I am trying to port a programme written in Maude, which is a reflective > language based on rewriting logic ( http://ma

Re: [Haskell-cafe] let vs. where

2007-11-15 Thread jeff p
Hello, > > taxRate = 0.06 > > total cart = subtotal + tax > where > subtotal = sum cart > taxable = filter isTaxable cart > tax = (sum taxable) * taxRate > > This example defines two functions, taxRate, which returns a constant > value, and total, which computes the total cost of t

[Haskell-cafe] job opportunity

2007-10-16 Thread jeff p
Hello, Here are the essential details... Location: NYC Industry: finance Salary: enough to live comfortably in Manhattan Hard Requirements: Must be able to work in the USA (we can't get you a worker's visa). Must be an expert level Haskell user; must be comfortable with monads, mona

Re: [Haskell-cafe] Can every monad can be implemented with Cont? (was: New slogan for haskell.org)

2007-10-13 Thread jeff p
Hello, > >> Didn't someone already prove all monads can be implemented in terms > >> of Cont? > >> > > > > Cont and StateT, wasn't it? > > And the schemers have no choice about running in StateT :) > > You sure? I want to see the proof :) > I think this is referring to Andrzej Filinski's paper "Re

[Haskell-cafe] latest hdbc-odbc

2007-10-10 Thread jeff p
Hello, When building the latest hdbc-odbc (1.1.2.0) on a linux box with ghc6.6.1, I get the following warnings: [7 of 7] Compiling Database.HDBC.ODBC ( Database/HDBC/ODBC.hs, dist/build/Database/HDBC/ODBC.o ) hdbc-odbc-helper.c: In function รข: hdbc-odbc-helper.c:131:0: w

Re: [Haskell-cafe] Composition Operator

2007-09-21 Thread jeff p
Hello, It's probably easiest to think of composition as a function which takes two arguments (both functions), (g :: b -> c) and (f :: a -> b), and returns a new function of type a -> c. We could write this explicitly as composition :: (b -> c, a -> b) -> a -> c composition (g,f) = \x ->

Re: [Haskell-cafe] HDBC Laziness (was Re: HDBC or HSQL)

2007-07-29 Thread jeff p
Hello, > I have heard from a number of people that this behavior is not very > newbie-friendly. I can see how that is true. I have an API revision > coming anyway, so perhaps this is the time to referse the default > laziness of HDBC calls (there would be a '-version of everything with > lazines

Re: [Haskell-cafe] HDBC or HSQL

2007-07-25 Thread jeff p
Hello, Would you go as far to say that when new programmers ask which database binding to use, we should _recommend_ HDBC then? (As we do gtk2hs, for the gui libraries). I'm not sure about this. Although I didn't extensively compare HSQL and HDBC, I got the impression that they offered roughl

Re: [Haskell-cafe] HDBC or HSQL

2007-07-25 Thread jeff p
Hello, I don't mean to hijack the thread. Does anyone have experience in using either HDBC or HSQL with Microsoft SQL server? I use HDBC with MS SQL Server, Sybase, and Oracle. I use the ODBC bindings. I am running on both a windows XP machine and a linux machine (although I haven't been able

[Haskell-cafe] hMapping polymorphic functions

2007-07-15 Thread jeff p
Hello, I am experimenting with type-level HList based programming. The Apply class: class Apply f a r | f a -> r where apply :: f -> a -> r apply = undefined -- In case we use Apply for -- type-level computations only -- Normal function applicat

[Haskell-cafe] Re: impossible to write type signature

2007-07-13 Thread jeff p
Hello, I finally found the thread I was looking for: http://www.haskell.org/pipermail/haskell-cafe/2006-December/020481.html Sorry for the noise. -Jeff On 7/14/07, jeff p <[EMAIL PROTECTED]> wrote: Hello, I managed to write a function, which ghc accepts, for which ghc rejects it

[Haskell-cafe] impossible to write type signature

2007-07-13 Thread jeff p
Hello, I managed to write a function, which ghc accepts, for which ghc rejects it's own type signature. I remember seeing a thread about this sometime in the last year or so, but I can't seem to find it. Does anyone remember this thread? thanks, Jeff ___

Re: [Haskell-cafe] Re: [Math] Category theory research programs?

2007-07-13 Thread jeff p
Hello, Since there were no replies about CS related category programs, I thought I'd point out a few notable places, and people, for category theory oriented CS. University of Pennsylvania has Peter Freyd in the math department, though he often collaborates with CS people. Carnegie Mellon Univ

Re: [Haskell-cafe] Re: Resolved: ffi linking problem

2007-06-01 Thread jeff p
Hello, No, it sounds like you're using the wrong import syntax. That linker warning is a dead givaway you should be using ccall, not stdcall. Ok. I just tried changing this and now things work fairly well. I thought stdcall was the correct syntax for windows. This seems like a strange state

[Haskell-cafe] Re: Resolved: ffi linking problem

2007-06-01 Thread jeff p
Hello, If -fvia-C fixes your problem, then your code has a bug, strictly speaking. If your foreign call requires some information from a header file, then the right way to call it is by making a small C wrapper function and calling that. I tried to do this but couldn't. I could get GHC to com

[Haskell-cafe] updating packages

2007-05-30 Thread jeff p
Hello, I just moved to ghc-6.6.1and was wondering if there is an automatic way to update the various packages I had installed previously. thanks, jeff ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/hask

Resolved: [Haskell-cafe] ffi linking problem

2007-05-30 Thread jeff p
Hello, In case anyone else finds this useful... My linking problem was finally resolved by using the -fvia-C flag when compiling with ghc. Thanks to Stefan O'Rear who pointed out the possibility and wrote: Does using -fvia-C help at all? The C compiler understands header files and is somet

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, No, but ghc does pass a lot of funny flags... Double check ccall v. stdcall in the import declaration. That bites a lot of people on Windows. My import statement originally looked like: foreign import ccall "mylib.h myFun" my_fun :: CDouble -> IO (Ptr CDouble) and my original lin

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, Thanks for the tips. I've gotten to the point where linking fails on an undefined reference. The strange thing about this is that when I make a C program to call the library function and compile with: myPrompt> gcc f.c mylib.lib everything works fine. I think ghc is using it's own ve

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, On 5/29/07, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> wrote: On May 29, 2007, at 23:01 , jeff p wrote: >myPrompt> ghc --make -fffi f.hs -l mylib.lib For historical reasons, you can't have a space between the -l and the library name. It's inserting an e

[Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, Can anyone give me some tips concerning the following error: myPrompt> ghc --make -fffi f.hs -l mylib.lib ghc --make -fffi f.hs -l mylib.lib [1 of 1] Compiling Main ( f.hs, f.o ) Linking f.exe ... d:\ghc\ghc6.6\gcc-lib\ld.exe: cannot find -l-Ld:/ghc/ghc6.6 c

Re: [Haskell-cafe] Re: Translating perl -> haskell, string "fill ins" with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-15 Thread jeff p
{ Hello, Here is a variation on Claus' code which returns an Either type rather than fails with error. This could be further generalized to use any instance of MonadError, rather than Either. -Jeff } import Control.Monad.Error financial_output :: String -> String -> String -> String

Re: [Haskell-cafe] >> and sequencing [newbie]

2007-04-15 Thread jeff p
Hello, On 4/15/07, David Powers <[EMAIL PROTECTED]> wrote: so... this is likely a question based on serious misunderstandings, but can anyone help me understand the exact mechanism by which monads enforce sequencing? Monads do not enforce sequencing. In general, data dependencies enforce sequ

Re: [Haskell-cafe] How to write elegant Haskell programms? (long posting)

2007-01-29 Thread jeff p
Hello, I think that whole "program flow" thing is something you get used to. In true, pure functional programming (i.e. Haskell) "program flow" is a meaningless term, basically. Haskell is a declarative language, not an imperative one. You have to learn to give up that control and trust the r

Re: [Haskell-cafe] Strings in Haskell

2007-01-23 Thread jeff p
Hello, On 1/23/07, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote: Tim Docker wrote: > I'm not aware of any ongoing haskell work in finance, other that > some private work being done by Alain Cremieux, reported in the HCAR. Lennart Augustsson works for Credit Suisse, using a Haskell DSEL to genera

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread jeff p
Hello, breakUp s | L.null s = [] | otherwise = h:(breakUp r) where (h,r) = L.splitAt 72 s Running this on the 2G file blows up the stack pretty quickly, taking the first 1 million records (there are 20M of them) with a big stack parameter gives about 25% producti

Re: [Haskell-cafe] Seeking advice on a style question

2006-12-24 Thread jeff p
Hello, Alternatively, I can wrap all of the state up into a single universal structure that holds everything I will ever need at every step, but doing so seems to me to fly in the face of strong typing; at the early stages of processing, the structure will have "holes" in it that don't contain u

Re: [Haskell-cafe] type hackery question

2006-12-17 Thread jeff p
Hello, I'm beginning to think what I'm after is not possible... I figure I should try to explain exactly what it is I'm after... Basically I'm trying to mix type hackery with HOAS. More specifically, here is a data type which I would like to use: data Exp a where Lam :: (Exp a -> E

Re: [Haskell-cafe] type hackery question

2006-12-17 Thread jeff p
Hello, Thanks for the response. > Is it possible to write a class which checks to see if two given type > arguments are unifiable? > This will probably help: http://www.haskell.org/pipermail/haskell-cafe/2006-November/019705.html That was Oleg's response to a post of mine: http://www.hask

[Haskell-cafe] type hackery question

2006-12-17 Thread jeff p
Hello, The HList paper gives a type cast: class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b instance TypeCast' () a b => T

Re: [Haskell-cafe] Trivial database access in Haskell

2006-12-11 Thread jeff p
Hello, 1. Simple documentation of how to install the library (starting from a vanilla GHC installation on Windows, plus Oracle software, to the point where I can use the library in my code). All I need is Oracle access, so other database client libraries can be ignored. I'd rather not use ODBC,

Re: [Haskell-cafe] generating javascript

2006-11-29 Thread jeff p
Hello, It sure should be possible to use HSPClientside with Text.XHtml, but off course with exceptions to all Haskell Server Pages (HSP) specific functions. Anyway I encourage you to have a look at HSP as well :-) It's quite nice to be able to use regular XML syntax within the Haskell code. C

Re: [Haskell-cafe] generating javascript

2006-11-28 Thread jeff p
Hello, There's a Google SoC-project made by a friend of mine for JavaScript support in Haskell Server Pages: http://csmisc14.cs.chalmers.se/~bjornson/soc/ It's a combinator library, but i'm not sure it's what you really need though. :) This seems to contain just what I was looking for. Altho

[Haskell-cafe] generating javascript

2006-11-28 Thread jeff p
Hello, Are there any Haskell tools to generate javascript? Has anyone made a combinator library for javascript? thanks, Jeff ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: optimization help

2006-10-17 Thread jeff p
Hello, Good, writeCSV writes out every row immediately after it got it. I eliminated (++ [nl]) in the hope of reducing the constant factor slightly. Using difference lists for that is nicer but here you go. I'm not sure how you'd use difference lists here. Also, for some reason GHC runs sligh

Re: [Haskell-cafe] Re: optimization help

2006-10-14 Thread jeff p
Hello, Yet, I'm a bit astonished. I thought that when compiling with -O2, cosmetic changes should become negligible. Perhaps the strict foldl' has an effect? Perhaps... but I doubt that is the main reason. At the moment I have no idea why there is such a discrepancy between the heap usages...

Re: [Haskell-cafe] Re: optimization help

2006-10-12 Thread jeff p
Hello, The (almost) point-free versions run faster than my "fast" imperative version and take up significantly less heap space-- even the version which reads everything and then writes takes up about 1/3 the heap space as my version. I get the impression that point-free style is a preventive m

Re: [Haskell-cafe] Re: optimization help

2006-10-12 Thread jeff p
Hello, When using addDate in foldM like below, you certainly don't want to search the cols for the string "Date" again and again everytime addDate is called. The index of the "Date" field is a number determined when parsing the header. That and only that number has to be plugged in here. Good

[Haskell-cafe] optimization help

2006-10-11 Thread jeff p
Hello, I have been trying to do some CSV-style processing. My code works fine for small input (up to 10MB), but performs poorly for moderate to large input (it can't seem to finish 100MB of input with 700MB heap space). I have gone through several optimization passes with profiler help, and now

Re: [Haskell-cafe] Greetings...

2006-09-29 Thread jeff p
Hello, So before I embark on day 1 of the project, I thought I should check and see if anyone on this list has used Haskell to munge a ten-million-row database table, and if there are any particular gotchas I should watch out for. One immediate thing to be careful about is how you do IO. Haske

Re: [Haskell-cafe] Slow IO

2006-09-09 Thread jeff p
Hello, Try Don Stewart's ByteString library (http://www.cse.unsw.edu.au/~dons/fps.html). It is much faster than the standard Haskell IO and now has lazy. -Jeff On 9/9/06, Daniel Fischer <[EMAIL PROTECTED]> wrote: Hello all, Now I have an IO-problem, too. SPOJ problem 41 asks basically to dete

[Haskell-cafe] graphics on mac os x

2006-02-23 Thread jeff p
Hello, I am running ghc 6.4.1 on mac os X (10.4.5). Can anyone give me some pointers for getting graphics functionality? I have tried wxhaskell, but it gives me the error HelloWorld.hs:4:0: Failed to load interface for `Graphics.UI.WX': Bad interface file: /usr/local/wxhaskell/lib/