[Haskell-cafe] Dependent types

2010-09-10 Thread Mitar
Hi!

I believe dependent types is the right term for my problem. I was
trying to solve it with GADTs but I was not successful so I am turning
to infinite (lazy) wisdom of Haskell Cafe.

I am attaching example code where I had to define MaybePacket data
type which combines different types of Packets I would like to allow
over Line. The problem is that there is a correlation between Line
type and MaybePacket type and I would like to tell Haskell about that.
But I am not sure how. Because now compiler, for example, warns me of
a non-exhaustive pattern even if some MaybePacket value is not
possible for given Line.

Somehow I would like to have a getFromFirstLine function which would
based on type of given Line return Maybe (Packet i) (for Line) or
Maybe AnyPacket (for LineAny). So that this would be enforced and type
checked.

Best regards and thanks for any help


Mitar


Test2.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Disable LINE Pragma handling in GHC

2010-09-10 Thread JP Moresmau
Hello fellow Haskellers,

In EclipseFP we use the GHC API for IDE related stuff like syntax
highlighting and code outlines. However, I ran into something funny
yesterday: when a source file contains LINE pragmas (
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/pragmas.html#line-pragma),
all the locations for tokens are changed to reflect the pragmas information.
While this is great in the normal' GHC usage, this is not so great for us,
because we're interested in that source code, not in original code. I
haven't seen any flag to turn that behavior off in the docs, nor in the
Lexer code, but have I missed something? Can I tell GHC to just ignore these
pragmas? I suppose even using GHC for building and something else
(haskell-src-exts?) for code handling would leave us with compilation
messages at the wrong place.

Thanks,

-- 
JP Moresmau
http://jpmoresmau.blogspot.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Will GHC 6.14 with LLVM use LLVM C compiler to compile external C Libraries

2010-09-10 Thread David Terei
2010/9/10 kyra ky...@mail.ru:
 I wonder if llvm-gcc supports it's own (gcc) extensions. If it supports then
 there is no need to stuck in clang right now.

It doesn't support the one I mentioned before of global register
variables. I haven't looked for a while so maybe this has changed but
llvm-gcc used to incorrectly claim that it supported this feature
simply because it supported the syntax. The actual implementation of
the extension doesn't work anything like gcc though so most code using
the feature will break if compiled with llvm-gcc. Global register
variables needs backend support (e.g register allocator) to be
implemented so llvm-gcc and clang are in the same boat here, both not
supporting it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dependent types

2010-09-10 Thread Stephen Tetley
On 10 September 2010 07:14, Mitar mmi...@gmail.com wrote:

 But I am not sure how. Because now compiler, for example, warns me of
 a non-exhaustive pattern even if some MaybePacket value is not
 possible for given Line.

This issue pops up quite quite often - Ryan Ingram's answer to it the
last time it was on the Cafe points to the relevant Trac issue
numbers:

http://www.haskell.org/pipermail/haskell-cafe/2010-August/082790.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: ecu-0.0.0

2010-09-10 Thread Stephen Tetley
On 10 September 2010 05:11, Tom Hawkins tomahawk...@gmail.com wrote:

 Another question: Can we get a Hackage category specifically for the
 use of Haskell in embedded systems?  I didn't see anything that stood
 out.


Hi Tom

Don't you just pick a category yourself in the Cabal file and Hackage
creates it when you upload?

Category:   Embedded


This is a bit prone to spam I suppose, but could be even worse for bad
spellers (like myself). Even at the moment, there seems to be some
discrepancy between categories named with the plural or the singular.

Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Style and a problem

2010-09-10 Thread Wanas
I should've mentioned that the maximum number in such a list is n. That's
why it stuck me as 'a bit' inexpensive.

\/\/

On Fri, Sep 10, 2010 at 5:02 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:


 On Sep 10, 2010, at 8:55 AM, Wanas wrote:

  Hey all,
 
  So I have a two part question (I'm new to haskell, so you can throw all
 your mugs at me).
 
  a) I want to write a function that generates lists of lists of size $n$.
 All having the property that sum lst = sum [1..n].
  a-1) After that, I want to remove all permutations. My idea of doing this
 is to get all lists from the first function and create a new list with the
 property that if sorted list A is not in the list, add it.

 It's not completely clear to me what you want.
 Here's my take on it:
S0 = {L | L is a list of positive integers and sum L = n}
L1 ~~ L2 iff L2 is a permutation of L1
 You want to enumerate S0/~~.

 Staring at this for a bit, what you want is
ENUMERATING THE PARTITIONS OF AN INTEGER.
 Look this up in almost any combinatorics book and you will find an
 algorithm that you can adapt.  There's stuff in Knuth, AOCP, Vol 4,
 for example.  A good reference is The Theory of Partitions, by
 G. E. Andrews, Cambridge University Press, 1998.

 Rung-Bin Lin has reported in Efficient Data Structures for Storing
 the Partitions of an Integer on a data structure for representing
 all the partitions of an integer n in O(n**2) space, taking O(n**2)
 time to construct it, so a list of lists might not be the best way
 to do it in Haskell.

 What you want to do is to generate the partitions in a canonical
 order with no duplicates in the first place.  Something along these
 lines:

 the partiions of n are
the partitions of n into pieces no bigger than n with [] appended.

 the partitions of n into pieces no bigger than k with xx appended are
the partitions of n-k into pieces no bigger than k with k::xx appended
  followed by
the partitions of n into pieces no bigger than k-1 with xx appended

 *with* some termination clauses which I haven't shown.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Combining applicative with arrows?

2010-09-10 Thread Nils Schweinsberg

Hey,


I just wondered if you can define Applicative instances for arrows? 
Basicly what I thought of is:


I have a type for my arrow which is CollectA (using HXT here):

type CollectA a = SomeArrow XmlTree a

And my datatype which I want to construct:

data Test = Test
{ testString:: String
, testInt   :: Int
}

With the functions:

collectString :: CollectA String
collectInt:: CollectA Int

Now, what I currently do is something like:

collectTest :: CollectA Test
collectTest = getChildren
   someOtherArrow  -- etc...
   proc foo - do
  s - collectString - foo
  i - collectInt- foo
  returnA - Test s i

With Applicatives that proc-do-part would become:

collectTest' :: CollectA Test
collectTest' = ... -- arrow stuff
Test $ collectString
* collectInt

Is something like this possible? I don't understand that proc part 
good enough to see what it's actually doing there, maybe someone with a 
better understanding for this could help out? :)



Thx,

- Nils
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Style and a problem

2010-09-10 Thread Wanas
On Fri, Sep 10, 2010 at 1:06 AM, Nils Schweinsberg m...@n-sch.de wrote:

 Something like this?

import Data.List

newList :: Int - [[Int]]
newList n = myNub
[ l | l - undefined -- not really sure how you want
 -- to generate these lists :)
, sum l == sum [1..n]
]

myNub :: (Ord a) = [[a]] - [[a]]
myNub = nubBy (\a b - sort a == sort b)


 - Nils

So I've checked out this code, and it doesn't compile on ghci. My version,
without the undefined portion is(which still doesn't work):

import Data.List

newList :: Int - [[Int]]
newList n = myNub [ l | l - [1..n], sum l == sum [1..n] ]

myNub :: (Ord a) = [[a]] - [[a]]
myNub = nubBy (\a b - sort a == sort b)

Maybe there's something in the syntax that I'm not quite getting...

\/\/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining applicative with arrows?

2010-09-10 Thread Ross Paterson
On Fri, Sep 10, 2010 at 10:34:04AM +0200, Nils Schweinsberg wrote:
 I just wondered if you can define Applicative instances for arrows?
 Basicly what I thought of is:
 
 I have a type for my arrow which is CollectA (using HXT here):
 
 type CollectA a = SomeArrow XmlTree a

If you do

  import Control.Applicative

  type CollectA = WrappedArrow SomeArrow XmlTree

then CollectA will be an instance of Applicative.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] malicious JS on haskell site

2010-09-10 Thread Ketil Malde
Albert Y. C. Lai tre...@vex.net writes:

 Looks like the free web counter was sold to an advertiser as few years ago.

I've seen this happen before, and it's just a strategy - first provide
some cross-site neat function, wait around for a while, then replace it
with some ad-serving crap.

Take home lesson: only serve JS that you host yourself.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FFI and concurrency

2010-09-10 Thread Johannes Waldmann
What's the story with FFI calls and concurrency?

I have an expensive calculation performed
by some C function, which I call from Haskell land.
(This works like a charm.)

I have several cores available. How could I run
several of these calculations in parallel?

Thanks, Johannes.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and concurrency

2010-09-10 Thread Bulat Ziganshin
Hello Johannes,

Friday, September 10, 2010, 2:25:58 PM, you wrote:

just forkIO in threaded RTS works for me. try:

main = do forkIO expensiveCalc
  forkIO expensiveCalc
  forkIO expensiveCalc
  expensiveCalc

 What's the story with FFI calls and concurrency?

 I have an expensive calculation performed
 by some C function, which I call from Haskell land.
 (This works like a charm.)

 I have several cores available. How could I run
 several of these calculations in parallel?

 Thanks, Johannes.


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disable LINE Pragma handling in GHC

2010-09-10 Thread Antoine Latter
On Fri, Sep 10, 2010 at 1:40 AM, JP Moresmau jpmores...@gmail.com wrote:
 Hello fellow Haskellers,
 In EclipseFP we use the GHC API for IDE related stuff like syntax
 highlighting and code outlines. However, I ran into something funny
 yesterday: when a source file contains LINE pragmas
 (http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/pragmas.html#line-pragma),
 all the locations for tokens are changed to reflect the pragmas information.
 While this is great in the normal' GHC usage, this is not so great for us,
 because we're interested in that source code, not in original code. I
 haven't seen any flag to turn that behavior off in the docs, nor in the
 Lexer code, but have I missed something? Can I tell GHC to just ignore these
 pragmas? I suppose even using GHC for building and something else
 (haskell-src-exts?) for code handling would leave us with compilation
 messages at the wrong place.
 Thanks,

Would you turn the behavior back on when editing .hsc files or
something similar?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disable LINE Pragma handling in GHC

2010-09-10 Thread JP Moresmau
Well, in an editor, there some operations that operate on solely on a file,
and some at the project level. I would make sense to me if typechecking
errors were reported against the original file (following the pragmas) while
lexing and outlining results would operate without (on the actual file
contents).

JP

On Fri, Sep 10, 2010 at 2:13 PM, Antoine Latter aslat...@gmail.com wrote:

 On Fri, Sep 10, 2010 at 1:40 AM, JP Moresmau jpmores...@gmail.com wrote:
  Hello fellow Haskellers,
  In EclipseFP we use the GHC API for IDE related stuff like syntax
  highlighting and code outlines. However, I ran into something funny
  yesterday: when a source file contains LINE pragmas
  (
 http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/pragmas.html#line-pragma
 ),
  all the locations for tokens are changed to reflect the pragmas
 information.
  While this is great in the normal' GHC usage, this is not so great for
 us,
  because we're interested in that source code, not in original code. I
  haven't seen any flag to turn that behavior off in the docs, nor in the
  Lexer code, but have I missed something? Can I tell GHC to just ignore
 these
  pragmas? I suppose even using GHC for building and something else
  (haskell-src-exts?) for code handling would leave us with compilation
  messages at the wrong place.
  Thanks,

 Would you turn the behavior back on when editing .hsc files or
 something similar?




-- 
JP Moresmau
http://jpmoresmau.blogspot.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dependent types

2010-09-10 Thread Mitar
Hi!

On Fri, Sep 10, 2010 at 9:22 AM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 This issue pops up quite quite often - Ryan Ingram's answer to it the
 last time it was on the Cafe points to the relevant Trac issue
 numbers:

But I have not yet made it as GADTs. I would need some help here. How
to change MaybePacket to GADTs?


Mitar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Style and a problem

2010-09-10 Thread Brent Yorgey
On Fri, Sep 10, 2010 at 12:24:39PM +0300, Wanas wrote:
 On Fri, Sep 10, 2010 at 1:06 AM, Nils Schweinsberg m...@n-sch.de wrote:
 
  Something like this?
 
 import Data.List
 
 newList :: Int - [[Int]]
 newList n = myNub
 [ l | l - undefined -- not really sure how you want
  -- to generate these lists :)
 , sum l == sum [1..n]
 ]
 
 myNub :: (Ord a) = [[a]] - [[a]]
 myNub = nubBy (\a b - sort a == sort b)
 
 
  - Nils
 
 So I've checked out this code, and it doesn't compile on ghci. My version,
 without the undefined portion is(which still doesn't work):
 
 import Data.List
 
 newList :: Int - [[Int]]
 newList n = myNub [ l | l - [1..n], sum l == sum [1..n] ]

The reason this doesn't compile is that 

  l - [1..n]

means l will take on each of the values 1 through n in turn.  So l is
of type Int.  But then you do 'sum l' which requires l to be a list.
So clearly that does not typecheck.  But I'm not quite sure I
understand what you actually want l to be.  Do you want it to run
through all lists of a certain length with elements chosen from
[1..n]?  In that case you could do something like

  import Control.Monad  -- for replicateM

  ...

  [ l | l - replicateM n [1..n], ... ]

which will generate all length-n lists with elements chosen from
[1..n].  If you wanted all lists with lengths from 1 to n and elements
chosen from 1 to n, you could do

  [ l | len - [1..n], l - replicateM len [1..n], ... ]

As others have pointed out there are likely far more efficient ways to
do what you want, but I'm just trying to help you get this code to
work first, even if it's inefficient.

-Brent

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: ecu-0.0.0

2010-09-10 Thread Brent Yorgey
On Thu, Sep 09, 2010 at 11:11:33PM -0500, Tom Hawkins wrote:
 to other fields, not just automotive.  My question is, is it possible
 for a user to select which programs to install within a given package?
  I could see where someone would want to install a data analysis tool,
 but not want to bother with separately installing Kvaser canlib.  I
 had considered different packages for the individual tools, but that
 would get messy pretty quick, especially since many tools share a lot
 of common code.
 
 And one last question:  The Kvaser canlib library has a different name
 depending on if the machine is Linux or Windows.  What is the best way
 to configure the build based on the platform?  Current I have the
 library name hard coded in the extra-libraries field in the cabal
 file.

You want conditional configurations in the .cabal file.  See

  
http://www.haskell.org/cabal/release/cabal-latest/doc/users-guide/authors.html#configurations

For the OS issue you can do something like

  if os(windows)
Build-depends: canlib-windows
  else
Build-depends: canlib

or whatever.  For user-selectable programs, create some flags and use
the flags to specify which executables are buildable.  Then the user
can just pass a flag to cabal install and get the executables they
want.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: DSTM 0.1.1

2010-09-10 Thread Frank Kupke
Here, the paper is now. You can download it from here 
http://www-ps.informatik.uni-kiel.de/~frk/dstm.pdf.
It is one pdf file. The first part is the paper, the second part is the manual 
that has been there before.

Regards,
Frank

Am 04.08.2010 um 15:55 schrieb Frank Kupke:

 Good questions. I am about to write a paper explaining the design of the DSTM 
 library in more detail which I will link when available. Please bear with me, 
 here. In the meantime please find some shorter answers below.
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: text-icu 0.4.0.0

2010-09-10 Thread Bryan O'Sullivan
The text-icu library is the more practical cousin to the text library,
implementing a myriad of Unicode-related functionality that is not yet
otherwise available in Haskell. It is implemented as bindings to the widely
used ICU library.

http://hackage.haskell.org/package/text-icu

Features:

   - Locale sensitive case mapping.
   - Text normalization. (What is normalization?
   http://unicode.org/faq/normalization.html)
   - [NEW] Locale sensitive string collation.
   - Conversion to and from a huge number of native encodings.
   - [NEW] Efficient comparison of ByteString and Text.

The library is thoroughly documented, and most interfaces are pure and easy
to use.

Look for further releases over the coming weeks as I complete the ICU
integration.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] re: Oracle stored procedures

2010-09-10 Thread Peter Marks
Hi Leonel

Thanks for your response. I don't know much about Oracle, but it has been
suggested that this approach of calling a stored procedure via SQL won't
work on a database that has security locked down to ensure all database
access is via stored procedures. All our production databases are locked
down in this way.

I'm told there is a different API call to call a stored procedure directly
rather than compile a SQL statement that calls the procedure. I'm guessing,
from your suggestion below, that Takusen does not expose this call?

I've taken an alternative route. We have our own Haskell to COM bridge (that
we hope to release at some point) and I'm using that to talk to ADO,
Microsoft's database API - yes, we are constrained to Windows for this.
Initial signs are positive, but I haven't finished it yet.


Peter

On 9 September 2010 06:13, Leonel Fonseca leone...@gmail.com wrote:

 Hi Peter,

 Yes, from Takusen you can call Oracle stored procedures, functions,
 packaged stored procedures or functions, or execute an arbitrary
 pl/sql block.

 In the Takusen software release there is a directory called
 Database\Oracle\Test. There,  Enumerator.lhs, among other code has
 these helpers you may want to use:


 wrapPLSQLFunc funcname parms =
   let sqltext = begin  ++ (head args) ++  :=  ++ funcname
  ++ ( ++ placeholders ++ ); end;
   placeholders = concat (intersperse , (tail args))
   args = take (length parms) (map (\n - :x ++ show n) [1..])
   in  cmdbind sqltext parms

 wrapPLSQLProc procname parms =
   let sqltext = begin  ++ procname
  ++ ( ++ placeholders ++ ); end;
   placeholders = concat (intersperse , args)
   args = take (length parms) (map (\n - :x ++ show n) [1..])
   in  cmdbind sqltext parms


 Please, be aware of the following points:

 1) If the pl/sql code doesn't need parameters and has no results, you
 can use execDDL. (execDML returns a counter of affected rows).
 2) If the procedure/function receives parameter, you'll need to use
 cmdbind (or similar to cmdbind) to pass the parameters.
 3) If the pl/sql code returns values, you have this options:
 3.a) The returned value is a reference (cursor): Takusen supports
 this very fine. Use doQuery or similar.
 3.b) The return value is an scalar value: You can collect the
 result with an iteratee, even if it is a single value.
 3.c) The return value is a complex oracle object: As of Takusen
 0.8.5 there is no support for table of records of ...
3.d) The return value is Boolean. You'll get an error.

 Little examples:

 For case #1:

  -- Example 1.a:  We set nls_language to  american english.
  set_NlsLang_Eng :: DBM mark Session ()
  set_NlsLang_Eng =  execDDL $ sql
   alter session set nls_language='AMERICAN'

  -- Example #1.b: Now we set session language parameter to spanish.
  set_NlsLang_Esp :: DBM mark Session ()
  set_NlsLang_Esp =  execDDL $ sql
   alter session set nls_language='LATIN AMERICAN SPANISH'

 For case #2:

  -- Example 2.a: We use database string concat function
 concat'  ::  String - String - DBM mark Session String
 concat' a b  =   do
let ite :: Monad m = String - IterAct m String
ite v _ = return $ Left v
sqlcmd = wrapPLSQLFunc concat
   [bindP $ Out (::String), bindP a, bindP b]
doQuery sqlcmd ite undefined
 
  -- later on the program, you'd have...
  some_string - concat' a b

 For case #3:

  -- Case 3.b: We collect a single scalar value.
  qNlsLang   ::  DBM mark Session [String]
  qNlsLang   =   doQuery s ite []
   where
   s   =   select value from nls_session_parameters \
   \ where parameter = 'NLS_LANGUAGE'
   ite ::  (Monad m) = String -  IterAct m [String]
   ite a acc = result' ( a:acc )

  mostrar_NlsLang  ::  DBM mark Session ()
  mostrar_NlsLang  =   qNlsLang = liftIO . print . head

  -- Another example for Case 3.b
  -- This time we don't use a list to accumulate results.
  s1 =  sql select systimestamp from dual
 
  sysTSasCTQ   ::  DBM mark Session CalendarTime
  sysTSasCTQ=  do
 
 let ite :: (Monad m) = CalendarTime - IterAct m CalendarTime
 ite x  _  =  result' x
 
 t -  liftIO ( getClockTime = toCalendarTime)
 doQuery s1 ite t


 --

 Leonel Fonseca.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] types for parsing a tree

2010-09-10 Thread Jared Jennings
Dear haskell-cafe:

I'm trying to parse an Open Financial eXchange (OFX) 1.x file. It
details my bank transactions, like debit card purchases. It's
SGML-based and it goes like:

OFX[...]
STMTRS[...]
STMTTRN[...]
TRNUID9223ry29r389
NAMETHE GROCERY STORE BLABLABLA
TRNAMT234.99
/STMTTRN
STMTTRN[...]
TRNUID1237tg832t
NAMESOME DUDE ON PAYPAL 4781487
TRNAMT2174.27
/STMTTRN
/STMTRS
/OFX

I've left out a bunch, but as you can see it's tree-shaped, and the
only reason they didn't misuse XML as a data serialization language
instead of SGML was because it wasn't popular yet. (OFX 2.x uses XML
but my bank doesn't use OFX 2.x.)

When I imagine how to put this into a data structure, I think:

-- The '...' below is stuff like the date, info about the bank
data OFX = OFX { statement :: StatementResponse, ... }
-- The '...' below is stuff like the account number
data StatementResponse = StatementResponse { transactions:
[Transaction], ... }
data Transaction = Transaction { id :: String, name :: String,
amount :: Decimal, sic :: Maybe Int, ... }

Then I tried to make a parser to emit those data types and failed. I
come from Python, where there's no problem if a function returns
different types of values depending on its inputs, but that doesn't
fly in Haskell.

I've tried

data OFXThing = OFX { statement :: OFXThing } | StatementResponse
{ ... transactions :: [OFXThing] }

but that would let me make trees of things that make no sense in OFX,
like a transaction containing a statement.

I made a

 data Tree k v = Branch k [Tree k v] | Leaf k v
 type TextTree = Tree String String

and a tagsoup-parsec parser that returns Branches for tags like OFX,
and Leafs for tags like TRNUID. But now I just have a tree of strings.
That holds no useful type information.

I want my types to say that OFXes contain statements and statements
contain transactions - just like the OFX DTD says. How can I construct
the types so that they are tight enough to be meaningful and loose
enough that it's possible to write functions that emit them?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haddock comments for GADT constructors?

2010-09-10 Thread Conal Elliott
I'm updating a library (TV) and getting haddock parse errors for the doc
strings attached to GADT constructors.  Is there a way to haddock-document
GADT constructors?  I've tried both -- | ... before and -- ^ ... 
after.  Both give parse errors.  Thanks,  - Conal
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haddock comments for GADT constructors?

2010-09-10 Thread David Waern
2010/9/10 Conal Elliott co...@conal.net:
 I'm updating a library (TV) and getting haddock parse errors for the doc
 strings attached to GADT constructors.  Is there a way to haddock-document
 GADT constructors?  I've tried both -- | ... before and -- ^ ... 
 after.  Both give parse errors.  Thanks,  - Conal

Nope. It's not yet supported. We should really get this one done.

http://trac.haskell.org/haddock/ticket/43

David
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] types for parsing a tree

2010-09-10 Thread Stephen Tetley
On 10 September 2010 17:53, Jared Jennings jjenn...@gmail.com wrote:

 I've tried

    data OFXThing = OFX { statement :: OFXThing } | StatementResponse
 { ... transactions :: [OFXThing] }

 but that would let me make trees of things that make no sense in OFX,
 like a transaction containing a statement.


Using alternative constructors (i.e. sum types) is the right approach
to get different datatypes in the tree. However you aren't
respecting the nesting of the tree here - OFX is a level higher in
the tree than a statement response and the OFX constructor recurs on
itself which looks suspect.

I suspect OFX is pathologically huge format and isn't a good starting
point for designing syntax trees (the downloadable Spec seemed to be
several megabytes zipped). If the DTD is very large you might want to
use the untyped tree to extract parts of interest and convert after
parsing to a smaller typed tree (with only the syntax you are
interested in).

By the way, HaXML has has a tool called DTD2HS (I think) that will
generate Haskell datatypes from a DTD definition.

Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Compile Glade apps (MS Windows system) Was: Re: Trying to compile Glade Gtk2Hs demo / cabal install glade problem

2010-09-10 Thread Daniel Kahlenberg
Hello,

I'm searching for information on a solution that must have been found
earlier on the list and somehow must have got lost, but have a look now
please...

On 14.08.2010 00:47, Peter Schmitz wrote:
 Thanks so very much Axel and Ivan.
 You were both absolutely correct and I can compile Glade apps now fine.
 Great help!
That's sounds very promising. Lucky you! Would you share the information
with the list - at least I'm really interested in how getting exactly
this done.
 The tricky part (for me) would have been looking at the error from
 cabal install glade:
   setup.exe: The pkg-config package libglade-2.0 version =2.0.0
 is required but it could not be found.
 and determining that the problem was that libglade-2.0.pc needed the
 edit you described,
 but I made the edit and it all works now.
 
 -- Peter
 ...
 New cabal install glade after libglade-2.0.pc edit:
Would you share information about that?? See my comment above...

Thanks for reading
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haddock comments for GADT constructors?

2010-09-10 Thread Conal Elliott
Thanks David.  Glad to know.  I'll kludge around the missing feature for
now.  I've added myself to the CC list for the ticket.  Regards,   - Conal

On Fri, Sep 10, 2010 at 10:47 AM, David Waern david.wa...@gmail.com wrote:

 2010/9/10 Conal Elliott co...@conal.net:
  I'm updating a library (TV) and getting haddock parse errors for the doc
  strings attached to GADT constructors.  Is there a way to
 haddock-document
  GADT constructors?  I've tried both -- | ... before and -- ^ ... 
  after.  Both give parse errors.  Thanks,  - Conal

 Nope. It's not yet supported. We should really get this one done.

 http://trac.haskell.org/haddock/ticket/43

 David

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] types for parsing a tree

2010-09-10 Thread S. Doaitse Swierstra
I show how this can be done using uu-parsinglib. Note that we have sevral 
parsers, each having its own type:

module Transactions where
import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.Examples
import Data.Char

pTagged tag (pAttr, pPayload) =  pToken ( ++ tag ++ ) * pAttr * spaces 
* pPayload * spaces *
 pToken (/ ++ tag ++ )
pTagtag pPayload  =  pToken ( ++ tag ++ ) * pPayload

data OFX = OFX Response deriving Show
data Response= Response [Transaction] deriving Show
data Transaction = Transaction String String Amount deriving Show
data Amount  = Amount Int Int deriving Show

pAmount  = TRNAMT   `pTag` (Amount $ pNatural * pSym '.' * 
pNatural)
pTransaction = STMTTRN  `pTagged` (pAttr, Transaction $  TRNUID 
`pTag` pLine
*  NAME   
`pTag` pLine
* pAmount
)
pResponse= STMTRS   `pTagged` (pAttr, Response $ pList 
(pTransaction * spaces))
pOFX = OFX  `pTagged` (pAttr, OFX  $ pResponse )

pAttr :: Parser String
pAttr = pToken [...]

spaces = pMunch (`elem`  \n\t)
pDigitAsInt = digit2Int $ pDigit 
pNatural = foldl (\a b - a * 10 + b ) 0 $ pList1 pDigitAsInt
digit2Int a =  ord a - ord '0'
pDigit :: Parser Char
pDigit = pSym ('0', '9')
pLine  = pMunch (/='\n') * spaces

main = do input - readFile TrInput
  run (pOFX * spaces) input

Running the main function on your code gives:

*Transactions :r
[1 of 1] Compiling Transactions ( Transactions.hs, interpreted )
Ok, modules loaded: Transactions.
*Transactions main
--
--  Result: OFX (Response [Transaction 9223ry29r389 THE GROCERY STORE 
BLABLABLA (Amount 234 99),Transaction 1237tg832t SOME DUDE ON PAYPAL 
4781487 (Amount 2174 27)])
-- 
*Transactions 

It is interesting to what happens if your input is incorrect,

 Doaitse





On 10 sep 2010, at 18:53, Jared Jennings wrote:

 OFX[...]
STMTRS[...]
STMTTRN[...]
TRNUID9223ry29r389
NAMETHE GROCERY STORE BLABLABLA
TRNAMT234.99
/STMTTRN
STMTTRN[...]
TRNUID1237tg832t
NAMESOME DUDE ON PAYPAL 4781487
TRNAMT2174.27
/STMTTRN
/STMTRS
/OFX

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disable LINE Pragma handling in GHC

2010-09-10 Thread Ben Millwood
On Fri, Sep 10, 2010 at 7:40 AM, JP Moresmau jpmores...@gmail.com wrote:
 I suppose even using GHC for building and something else
 (haskell-src-exts?) for code handling would leave us with compilation
 messages at the wrong place.

I don't quite understand your use case so I'm not sure it helps, but
for what it's worth haskell-src-exts allows you to ignore line pragmas
while parsing:

http://hackage.haskell.org/packages/archive/haskell-src-exts/1.9.0/doc/html/Language-Haskell-Exts-Parser.html#t:ParseMode
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disable LINE Pragma handling in GHC

2010-09-10 Thread Henk-Jan van Tuyl
On Fri, 10 Sep 2010 08:40:22 +0200, JP Moresmau jpmores...@gmail.com  
wrote:



Can I tell GHC to just ignore these
pragmas? I suppose even using GHC for building and something else
(haskell-src-exts?) for code handling would leave us with compilation
messages at the wrong place.

Thanks,



Maybe you could try something like

#ifdef USE_LINE_PRAGMAS
{-# LINE 42 Foo.lhs #-}
#endif

Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Restricted type classes

2010-09-10 Thread wren ng thornton

On 9/10/10 12:47 AM, David Menendez wrote:

It seems like you could use a similar argument to show that fmap id /= id.

Specifically, xs and map id xs are equivalent lists, but they occupy
different locations in memory. By replacing xs with map id xs, you can
come arbitrarily close to doubling a program's memory requirements.
(You can also use pointer comparison to distinguish them, but I assume
that doesn't count.)


That doesn't really follow. The Haskell values and types do not capture 
heap transformations, so those don't count for the same reason that 
pointer equality doesn't count.


The fmap id = id law only needs to apply at each use site, not 
necessarily when doing whole-program analysis. Given any list xs, it is 
indeed true that the result of (fmap id xs) is equal to the result of 
(id xs). They even take up the same amount of space after full 
evaluation. The only difference is that the latter avoids some extra 
allocation and garbage collection and preserves sharing, none of which 
is captured by the type system. Indeed, that's why we'd like to know the 
laws hold, so that we can rewrite occurences of (fmap id) with id; just 
as we'd like to replace (fmap f . fmap g) by fmap(f.g) since it improves 
time performance by only performing a single traversal. Time is also not 
captured by the type system. Technically we could rewrite programs in 
the other direction and introduce new fmaps, we just have no reason to 
do so.


However, in the example I gave, the actual values (E (f a) a) and (E (f 
a) (f a)) are not equal even when ignoring time, space, and sharing. 
They may be *isomorphic* because they have the same observable behavior 
within the language (assuming no polymorphic seq or heap-size 
reflection), but they are not *equal*. Your comments about increasing 
total-program allocation just points out that (fmap id) and id are not 
*identical*--- which we know already. But even if they cannot be 
identical, they must be equal if the fmap instance is lawfully a 
functor. The notions of being identical, equal, isomorphic, and 
equivalent are all quite different. I was only using the size of their 
heap representation as evidence for the non-equality of these two terms 
in spite of their isomorphism.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] gathering position information lazily using traverse

2010-09-10 Thread Jan Christiansen

Dear Applicative experts,

I am seeking advice on Applicative instances and their use in  
traverse. Consider the following Applicative instance.


  newtype Proj a = Proj { unProj :: [Bool] - a }

  instance Functor Proj where
fmap g (Proj f) = Proj (g . f)

  instance Applicative Proj where
pure = Proj . const
Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

In fact, this is not an Applicative instance as it does not satisfy  
the laws. On basis of this instance I have defined the following  
function.


  gshape :: Traversable t = t a - t [Bool]
  gshape x = unProj (traverse (const (Proj reverse)) x) []

The idea is simply to replace every polymorphic component by an  
identifier that identifies the position of the component in the data  
structure. That is, provided with the identifier I want to be able to  
project to the corresponding component. In this case this identifier  
is a path in the idiomatic term from the root to the component.


I can define a correct Applicative instance if I add an additional  
constructor, which represents pure. I did not prove that it satisfies  
all laws but I think it does.


  data Proj a = Pure a | Proj ([Bool] - a)

  instance Functor Proj where
fmap g (Pure x) = Pure (g x)
fmap g (Proj f) = Proj (g . f)

  instance Applicative Proj where
pure x = Pure x
Pure f * Pure x = Pure (f x)
Pure f * Proj x = Proj (\p - f (x p))
Proj f * Pure x = Proj (\p - f p x)
Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

My problem is that this correct instance is too strict for my purpose.  
It is important that gshape operates correctly on partial data, that  
is, even if its argument is partial all the components should be  
replaced correctly. For example, we have


  gshape (Node _|_ 0 (Leaf 1))) = Node _|_ [False,True] (Leaf [True])


If the applicative instance performs pattern matching, like the latter  
instance, then gshape is too strict. Therefore I suspect that there is  
no correct Applicative instance that satisfies my needs but I am not  
at all certain.


Thanks, Jan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] gathering position information lazily using traverse

2010-09-10 Thread Felipe Lessa
H...

On Fri, Sep 10, 2010 at 6:47 PM, Jan Christiansen
j...@informatik.uni-kiel.de wrote:
  instance Applicative Proj where
    pure = Proj . const
    Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

  (pure f) * Proj x
   === Proj (const f) * Proj x
   === Proj (\p - (const f) (False:p) (x (True:p)))
   === Proj (\p - f (x (True:p)))

  Proj f * (pure x)
   === Proj f * Proj (const x)
   === Proj (\p - f (False:p) ((const x) (True:p)))
   === Proj (\p - f (False:p) x))

  instance Applicative Proj where
    pure x = Pure x
    Pure f * Pure x = Pure (f x)
    Pure f * Proj x = Proj (\p - f (x p))
    Proj f * Pure x = Proj (\p - f p x)
    Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

  (pure f) * Proj x
   === Pure f * Proj x
   === Proj (\p - f (x p))

  (Proj f) * (pure x)
   === Proj f * Pure x
   === Proj (\p - f p x)

Was this difference intended?

Cheers! =)

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] gathering position information lazily using traverse

2010-09-10 Thread Jan Christiansen


On 10.09.2010, at 23:58, Felipe Lessa wrote:


H...

On Fri, Sep 10, 2010 at 6:47 PM, Jan Christiansen
j...@informatik.uni-kiel.de wrote:

 instance Applicative Proj where
   pure = Proj . const
   Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))


 (pure f) * Proj x
  === Proj (const f) * Proj x
  === Proj (\p - (const f) (False:p) (x (True:p)))
  === Proj (\p - f (x (True:p)))

 Proj f * (pure x)
  === Proj f * Proj (const x)
  === Proj (\p - f (False:p) ((const x) (True:p)))
  === Proj (\p - f (False:p) x))


 instance Applicative Proj where
   pure x = Pure x
   Pure f * Pure x = Pure (f x)
   Pure f * Proj x = Proj (\p - f (x p))
   Proj f * Pure x = Proj (\p - f p x)
   Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))


 (pure f) * Proj x
  === Pure f * Proj x
  === Proj (\p - f (x p))

 (Proj f) * (pure x)
  === Proj f * Pure x
  === Proj (\p - f p x)

Was this difference intended?


Yes, this is intended. This difference is the reason why the former  
instance does not satisfy the Applicative laws while the latter does.


The first instance provides every subterm of an idiomatic term with a  
position. Even a pure term is provided with a position although it  
does not use it. The latter instance does not provide a pure term  
with a position as it does not need one. Therefore, the second  
instance simply passes position p to a subterm if the other subterm is  
pure. In the example for the first instance we can observe that we  
unnecessarily extend the position with True and False respectively.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Restricted type classes

2010-09-10 Thread Dan Doel
On Wednesday 08 September 2010 11:17:43 pm wren ng thornton wrote:
  -- | Proof that impure is not p...@e
  fmap f (impure a)
  == fmap f (E a a)
  == E (f a) a
  /= E (f a) (f a)
  == impure (f a)

I don't believe your proof. The type of E is as follows:

  E :: a - b - E a

The free theorem given by that type is:

  forall f g x y. map f (E x y) = E (f x) (g y)

Setting y = x and g = f, we get:

  forall f x. map f (E x x) = E (f x) (f x)

So your above proof simply assumes that parametricity can be refuted. seq may 
cause that, but without seq, one would expect parametricity to hold, or at 
least not be refutable (unless there are other notorious examples I'm failing 
to remember; existential types aren't one).

I think the core of this is your ensuing discussion about equality versus 
equivalence. You seem to be advancing the notion that equality can only be 
used to refer to intensional equality. But intensional equality doesn't work 
very well for existential types, and up to extensional equality, the above 
should hold. Further, even with intensional equality, one wouldn't expect to 
be able to prove that E (f a) a /= E (f a) (f a). We should merely not be able 
to prove that  E (f a) a = E (f a) (f a).

Going back to free theorems, the theorem for:

  pure :: a - T a

is

  map f . pure = pure . f

so any proposed counter example to that must be a refutation of parametricity 
for the language in question. I can believe that seq will produce refutations. 
Any proposal in which existential types do the same parametricity seems to me 
like it should be rethought.

-- Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Google AI Challenge: Planet Wars - Accepting Haskell Submissions

2010-09-10 Thread Jake McArthur
Just wanted to let everybody know that there is an AI contest [1] that 
started today. Everybody has about two months to create bots that 
compete against each other 1-on-1 in a game based on Galcon [2].


A couple issues to mention for full disclosure: There is some 
sponsorship by Google, but unfortunately they aren't running the 
hardware, so the site is getting pretty hammered right now. We (it's all 
open source and open for contributions) are working to get it optimized 
to better handle the load. Also, the version of GHC on the server is 
very old (6.8.2) and isn't likely to get updated. I'm working to allow 
binary submissions though. If that goes through, you guys will be able 
to submit 64-bit Linux binaries rather than Haskell code to be compiled 
on the server.


Just letting everybody know so the Haskell community can represent!

- Jake

[1] http://ai-contest.com
[2] http://galcon.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Google AI Challenge: Planet Wars - Accepting Haskell Submissions

2010-09-10 Thread Alex Kropivny
The previous AI challenge (tron) was a lot of fun. I suspect the
experience they gained from running the last one, will make this an
exciting contest.

Haskell fared well in the last contest, despite it favouring fast
C/C++ implementations due to a focus on classic minimax/pruning. The
current challenge looks more open-ended as far as solutions go, so
hopefully there'll see even more Haskell submissions! :)

On Fri, Sep 10, 2010 at 4:11 PM, Jake McArthur jake.mcart...@gmail.com wrote:
 Just wanted to let everybody know that there is an AI contest [1] that
 started today. Everybody has about two months to create bots that compete
 against each other 1-on-1 in a game based on Galcon [2].

 A couple issues to mention for full disclosure: There is some sponsorship by
 Google, but unfortunately they aren't running the hardware, so the site is
 getting pretty hammered right now. We (it's all open source and open for
 contributions) are working to get it optimized to better handle the load.
 Also, the version of GHC on the server is very old (6.8.2) and isn't likely
 to get updated. I'm working to allow binary submissions though. If that goes
 through, you guys will be able to submit 64-bit Linux binaries rather than
 Haskell code to be compiled on the server.

 Just letting everybody know so the Haskell community can represent!

 - Jake

 [1] http://ai-contest.com
 [2] http://galcon.com
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dependent types

2010-09-10 Thread Mitar
Hi!

I made it. ;-)

Thanks to all help from copumpkin on IRC channel.

I am attaching my solution for similar problems in future. And of
course comments.


Mitar


Test5.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cost: (:) vs head

2010-09-10 Thread michael rice
Which of these would be more costly for a long list?

f :: [Int] - [Int]
f [x] = [x]
f (x:xs) = x + (head xs) : f xs

f :: [Int] - [Int]

f [x] = [x]

f (x:y:xs) = x + y : f (y:xs)

Michael






  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cost: (:) vs head

2010-09-10 Thread Dan Doel
On Friday 10 September 2010 11:13:50 pm michael rice wrote:
 Which of these would be more costly for a long list?
 
 f :: [Int] - [Int]
 f [x] = [x]
 f (x:xs) = x + (head xs) : f xs
 
 f :: [Int] - [Int]
 
 f [x] = [x]
 f (x:y:xs) = x + y : f (y:xs)

Another option would be:

  f [x] = [x]
  f (x:xs@(y:_)) = (x + y) : f xs

However, I believe I've done tests in the past, and your second example 
generates the same code when optimizations are on (that is, it doesn't build a 
new y:xs, but reuses the existing one), and that should perform the same as 
your first implementation.

All that said, I'm not sure you'd be able to see the difference anyway.

-- Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] re: Oracle stored procedures

2010-09-10 Thread Leonel Fonseca
Hi, Peter

I did and uploaded some examples regarding Oracle and Takusen and the
intended approach you would employ.

Example 01: Create table and some tuples.
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29883#a29883

Example 02: Create a package with procedures to mantain the table.
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29884#a29884

Example 03: Optional. See how it works in Oracle sqlplus.
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29885#a29885

Example 04: The Takusen-Haskell program. It follows the scheme of example #03.
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29894#a29894

Some comments on the topic:

This approach has limitations. Takusen (if not use in conjunction with
Template Haskell) will be bound up to iteratees of eight values. I
(and I'm pretty sure some other people) have successfully used
Template Haskell to overcome this limitation.
(I've been working in removing some boilerplate).

The all stored procedure approach is not a limitation as you can see
from example #04, unless these procedures return values these types:
Record Of something, complex objects (PL/SQL tables, objects, etc),
Boolean.

Oracle has several programatic interfaces, some that I remember: JDBC,
ODBC, OCI, OCCI and those for Windows .NET.

Takusen is a wrapper for OCI (Oracle Call Interface) which seems to me
pretty low level. Yet, I don't know if you can specify just the name
of the procedure.

Please note that if there is a procedure named close_accounts, by
writing begin close_accounts; end; you are not wrapping it in a SQL
statement. It actually is an anonymous PL/SQL block and it is needed
in that form to be processed by the server.

Oracle offers for Windows .NET: ODT (Oracle Developer Tools for Visual
Studio), ODP (Oracle Data Provider) and ODE (Oracle Database
Extensions). I did test (and taste) a bit of .NET tools with F#. It
was nice. Maybe you wish to try hs-dotnet with these.

A final remark, I have used Takusen both on Windows and Linux. The
given example was developed and tested actually on Windows.


Regards,

Leonel Fonseca.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe