Re: [Haskell-cafe] Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Andrea Rossato
On Thu, Jul 26, 2007 at 10:25:06PM -0700, Dave Bayer wrote:
  Ok, I'm writing a command line tool, using System.Console.GetOpt to handle 
  command line arguments. My Flags structure so far is
 
  data Flag
  = Filter String
  | DateFormat String
  | DocStart String
  | DocEnd String
  ...
 
  and I want to write accessor functions that return the strings if specified, 
  otherwise returning a default. The best I've been able to do is 

I don't know if my reply is going to be helpful to you. This is what I
would suggest: why don't you create a data type with label records,
and than you store that data type in a IORef and update the IORef. At
the end you just read the IORef with your updated data:

data Config = { filter :: String
  , dateFormat :: String
  , etc ...
  } 

Then you create a new IOref with config, and, with getOpt, you update
the IOref with modifyIORef. At the very end you read the modified
IOref.

This way you can have default options to be modified with command line
options.

I don't know if it is clear, but I adopted this approach in a program
I'm writing. A program with 14 command line options.

Have a look at this part here (starting from data Opts=):
http://gorgias.mine.nu/repos/xmobar/Main.hs

This way I can load a configuration file and change some of the
options, configured in that file, with the given command line options.

I hope this is going to help you.
Andrea
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Stuart Cook
On 7/27/07, Eric Y. Kow [EMAIL PROTECTED] wrote:
 Solution #3 No lists, just records (lhs2TeX)
 --

 Advantages:
   very convenient/compact; have to write
 (i)   Flag type
 (ii)  Settings record type/GetOpt in one go
 (iii) default Settings
   easy to lookup flags

 Disadvantages:
   Not as flexible
- can't group flags into blocks and have different programs that use
  different subsets of flags (without sharing the same Setting type)
- everything must go into Settings
- seems harder to say stuff like 'if flag X is set and flag Y are in
  the list of Flags, then parameterise flag Z this way' or
  'flags X and Y are mutually exclusive'

This is what I'm using for my current project. Most of the
disadvantages don't apply in my case, because all my flags are
largely-independent simulation parameters.

The one thing I find annoying, though, is that for each option I add,
I need to make changes in three places:

  1) The definition of my options record
  2) My default options value
  3) My list of GetOpt.OptDescr

What I'd really like to be able to do is specify the field name, field
type, and GetOpt info in a single place, without any redundancy. This
is obviously impossible in vanilla Haskell, so some kind of fancy
preprocessing or templating would be necessary. (Sadly, I'm not in a
position to pull this off right now.)


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


[Haskell-cafe] Re: Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Eric Y. Kow
Hi,

Here is a possible two part response.  Not literate code, just using 
to distinguish code from everything else.

A short answer
==
  getFilter = getString f Markdown.pl
  where f (Filter s) = Just s
f _ = Nothing
 
  getDateFormat = getString f %B %e, %Y
  where f (DateFormat s) = Just s
f _ = Nothing

For starters, you could squish these down into something like

 flagToString :: Flag - Maybe String
 flagToString (Filter s) = Just s
 flagToString (DateFormat s) = Just s
 ...
 flagToString _ = Nothing
 
Then you would have
 getFilter = getString flagToString Markdown.pl
 getDateFormat = getString flagToString %B %e, %Y
 
A long answer
=
I have noticed a lot of ways of dealing with GetOpt flags in Hakell
programs and thought it might be useful to catalogue them.  A lot of
this could be wrong btw, for example, advantages/disadvantages.  But I
think the general idea might be useful, so please add to this if you
see other solutions.

Solution #1 Ginormous record

Do you happen to have some giant recordful of command line parameters?
Something like

  data Settings = Settings { filter :: Maybe String
   , dateFormat :: Maybe String
   , blahBlah   :: Maybe Blah
   ...
   , thisIsGetting :: RatherLargeIsntIt
   }
  
  emptySettings :: Settings
  emptySettings = Settings { filter = Nothing
   , dateFormat = Nothing 
   }
 
  toSettings :: [Flag] - Settings
  toSettings fs = toSettingsH fs emptySettings
  
  toSettingsH :: [Flag] - Settings - Settings
  toSettingsH (Filter s:fs) i = toSettingsH fs (i { filter = s })
  toSettingsH (DateFormat s:fs) i = toSettingsH fs (i { dateFormat = i })
 
Note: You can make this a little less painful by factoring out the
recursion (took me a while to realise this!).

  toSettings fs = foldr ($) emptySettings (map processFlag fs)
 
  processFlag :: Flag - Settings - Settings
  processFlag (Filter s) i = i { filter = Just s }
  processFlag (DateFormat s) i = i { dateFormat = s }
  ...

Advantages:
  - simple, easy to look up settings

Disadvantages:
  boring; have to write
(i)   Flag type
(ii)  Settings record type
(iii) default Settings 
(iv)  processFlag entry
(v)   GetOpt entry

  record gets really really huge if you have a lot of flags

Solution #2 List of flags (darcs) 
-
Don't bother keeping any records around, just pass around a big list of
flags to functions that depend on settings.

if the flag has any parameters, you can't just write (DateFormat
`elem` fs); you'll have to write some boilerplate along the lines
of

 hasDateFormat :: [Flag] - Bool
 hasDateFormat (DateFormat s:fs) = True 
 hasDateFormat (_:fs) = hasDateFormat fs
 hasDateFormat [] = False 
 
 getDateFormat :: [Flag] - Maybe String
 getDateFormat (DateFormat s:fs) = Just s
 getDateFormat (_:fs) = getDateFormat fs
 getDateFormat [] = Nothing
 
which again can be factored out...

 fromDateFormat :: Flag - Maybe String
 fromDateFormat (DateFormat x) = Just x
 fromDateFormat _ = Nothing
 
 hasDateFormat fs = any (isJust.fromDateFormat) fs
 getDateFormat fs = listToMaybe $ mapMaybe fromDateFormat fs

Still, this is more pay-as-you-go in the sense that not all flags need
to be accessed, so maybe you end up writing less boilerplate overall

Advantages:
  simple
  very convenient to add flags (as a minimum, you have to write
(i)   flag type
(ii)  GetOpt entry
(iii) lookup code (but pay-as-you-go)

Disadvantages:
  still a bit boilerplatey

Solution #3 No lists, just records (lhs2TeX)
--
This one is due to Andres Löh, I think although my rendition of it may
not be as nice as his.

Ever considered that your Settings record could almost be your Flag
type?  The trick here is recognising that constructors are functions too
and what GetOpt really wants is just a function, not necessarily a
constructor.

 type Flag a = (a - Settings - Settings)
 
 options :: [OptDescr Flag]
 options =
   [ Option f [filter]
   (ReqArg (\x s - s { filter = Just x }) TYPE)
   blahblah
   , Option d [date-format]
   (ReqArg (\x s - s { dateFormat = Just x }) TYPE)
   blahblah
 
   ]

Advantages:
  very convenient/compact; have to write
(i)   Flag type
(ii)  Settings record type/GetOpt in one go
(iii) default Settings 
  easy to lookup flags
  
Disadvantages:
  Not as flexible
   - can't group flags into blocks and have different programs that use
 different subsets of flags (without sharing the same Setting type)
   - everything must go into Settings
   - seems harder to say stuff like 'if flag X is set and flag Y are in
 the list of Flags, then parameterise flag Z this way' or
 'flags X and Y are mutually 

[Haskell-cafe] Re: Indentation woes

2007-07-27 Thread Stefan Monnier
 I wish to be able to indent my code like so:
 longFunctionName various and sundry arguments
 | guard1 = body1
 | guard2 = body2
 | ...
 where declarations
 That is, with guards and where clauses indented to the same level as
 the function name.

Sounds like a generalization of the idea of allowing indentation like

 if foo then bar
 else baz

in `do' notation.  It might probably be obtained similarly by just adding
a few optional semi-colons at the right place in the BNF rules.  whether
those optional semi-colons will render the grammar significantly
more complex, I don't know.


Stefan


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


Re: Re : Re : Re : [Haskell-cafe] Indentation woes

2007-07-27 Thread Dougal Stanton
On 27/07/07, anon [EMAIL PROTECTED] wrote:

 I see what you did there. But you really might as well end sentences
 with prepositions. Or begin them with conjunction. Or indent your code
 whichever way seems most natural and elegant because to do otherwise
 is just prescriptivism for its own sake.

Natural and artificial languages cannot be compared on this level.
Programming languages, and Haskell in particular, are nearly entirely
prescriptive. In fact, if I remember rightly Haskell was originally
intended to be more prescriptive than most. It certainly has fewer
nasal demon clauses in the Haskell Report. This differs a great deal
from English, for example, which underwent a slow and undirected
evolution (unless there was an English Committee in 1550 set up to
decide the Great Vowel Problem...) from various parent languages,
themselves not designed either.

If you would *like* to use an arbitrary indentation I think unsugared
Haskell should allow that. Though it seems rather an uncomfortable
hair-shirt to wear for such little reward.

Cheers,

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


Re: [Haskell-cafe] Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Neil Mitchell
Hi

Why not:

 data Flag
   = Filter String
   | DateFormat String
   | DocStart String
   | DocEnd String

Becomes:

data Flag = Flag Key String
data Key = Filter | DateFormat | DocStart | DocEnd

getString :: Flag - Key - String
getString (Flag x y) key = if key == x then y else 

You can easily extend this to defaults:

defaults = [(DocStart,1)]

then lookup, instead of just  as the else clause.

If you have to use Data/Typeable you will no longer be writing
portable Haskell, and while they are great, they aren't the thing to
use here.

Thanks

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


RE: [Haskell-cafe] Handling custom types in Takusen

2007-07-27 Thread Bayley, Alistair
 I noticed that in Takusen there're just two instances to implement to
 make any Haskell type db-serializable: DBBind / SqliteBind for
 serialization and DBType for deserialization.
 
 I wanted to implement blob serialization for PackedStrings, but I
 noticed that both DBBind and DBType classes are not public.
 Defining custom serialization (not just Show  / Read string
 serialization) is very useful in applicative code, and not just in
 Takusen backend code.
 
 There's any way to do it without modifying Takusen Sqlite backend?
 
 Salvatore Insalaco

Sorry, not at present. It shouldn't be hard to modify the code though,
and PackedString support is something we should really be thinking about
anyway (as well as Blobs, which I think should have a different type).

Although DBType is a class in InternalEnumerator (so you'd think it
might be easy to extend with new types), in practice we do not expose
the internal Query and ColumnBuffer objects that you also need to create
new instances of the class, so you're stuck with what we provide. This
is intentional; you usually need to access the low-level buffers and
other resources to write an instance on DBType, and we don't want to
expose these details to users. By hiding this stuff, we can ensure that
resources are properly cleaned up when queries and commands complete.

So, please take this as an invitation to modity the Sqlite
implementation to handle PackedStrings (and Blobs, if you want to).

BTW, do you really need to marshall PackedStrings to blobs? The Sqlite
library uses CStrings, and I assume that CString to PackedString
marshaling is fairly efficient, so that would seem to be a better
choice. (I have no experience of PackedStrings, so there might be good
reasons to prefer blobs, and I'd like to know what they are.)

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Jonathan Cast
On Friday 27 July 2007, Dave Bayer wrote:
 Ok, I'm writing a command line tool, using System.Console.GetOpt to
 handle command line arguments. My Flags structure so far is

  data Flag
  = Filter String
 
  | DateFormat String
  | DocStart String
  | DocEnd String

 ...

 and I want to write accessor functions that return the strings if
 specified, otherwise returning a default. The best I've been able to

 do is this:
  getFilter = getString f Markdown.pl
  where f (Filter s) = Just s
f _ = Nothing
 
  getDateFormat = getString f %B %e, %Y
  where f (DateFormat s) = Just s
f _ = Nothing
 
  getDocStart = getString f ^{-$
  where f (DocStart s) = Just s
f _ = Nothing
 
  getDocEnd = getString f ^-}$
  where f (DocEnd s) = Just s
f _ = Nothing

 using a generic accessor function `getString`.

 There are eight (and growing) needless lines here, where what I
 really want to do is to pass the constructors `Filter`, `DateFormat`,
 `DocStart`, or `DocEnd` to the function `getString`. ghci types each
 of these as `String - Flag`, so one at least knows how to type such
 a `getString`, but using a constructor-passed-as-an-argument in a
 pattern match is of course a Parse error in pattern. (I expected as
 much, but I had to try... `String - Flag` is not enough information
 to make it clear we're passing a constructor, rather than some hairy
 arbitrary function, so such a pattern match would be undecidable in
 general.)

 So what's the right idiom for avoiding this boilerplate?

What you want can (almost) be done as follows:

{-# OPTIONS_GHC -fglasgow-exts #-}
import Data.Generics
import Data.Typeable

data Flag
  = Filter String
  | DateFormat String
  | DocStart String
  | DocEnd String
  deriving (Typeable, Data)

getString :: Flag - String - Flag - String
getString c df f | toConstr c /= toConstr f = df
getString c df (Filter s) = s
getString c df (DateFormat s) = s
getString c df (DocStart s) = s
getString c df (DocEnd s) = s

This version uses overlapping patterns, of course; it should be evident how to 
change that if you want.

Call it as

getString Filter{} Markdown.pl flag

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs


pgp7JvE0fRdTA.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Handling custom types in Takusen

2007-07-27 Thread Bayley, Alistair
 From: Salvatore Insalaco [mailto:[EMAIL PROTECTED] 
 
 The main reason is that I'm working on a Sqlite back-end for Darcs,
 that will be used to store file contents.
 I think to choose Takusen as back-end library mainly because it has
 the blob functions of Sqlite already mapped.

Umm, yes... I wrote the blob FFI imports for Sqlite, as I planned to
prototype Takusen's blob support in Sqlite first, but never got any
further with it. It is completely untested.


 In Darcs PackedStrings are used to store file contents in memory. I
 don't think that it would be very efficient to store files of
 megabytes in a text column (there could be encoding problems too).
 
 Also, in Sqlite 3.4, they introduced new functions for incremental
 reading / writing of Blobs. I could use them in the future.

Seems reasonable. I recall Oleg saying something privately a while ago
about an API for large objects. He may have some ideas for this.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Indentation woes

2007-07-27 Thread Steve Schafer
On Fri, 27 Jul 2007 00:33:17 -0400, you wrote:

What makes this a law? If you notice a pattern where beginners trip
against this rule because they don't indent the arms of conditionals
properly inside do blocks, should strict adherence to this principle
take precendence over the intuition of prospective users of the
language?

What exactly are you proposing as an alternative rule? If you're
suggesting that _any_ line at the same level of indentation as the
previous line be treated as a continuation of that line, then how would
one go about indicating that a line is _not_ a continuation of the
previous line?

On the other hand, if you're suggesting that only certain things be
recognized as being a continuation of the previous line (e.g., guard
clauses), then it seems to me that you're replacing a brain-dead simple
and straightforward rule with one that is inherently more complex and
thus more likely to cause angst among beginners.

Or are you proposing to get rid of layout altogether and rely on
punctuation?

I just can't think of a rule that would be easier to understand (and
quicker to assimilate) than the current one.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Handling custom types in Takusen

2007-07-27 Thread Salvatore Insalaco
2007/7/27, Bayley, Alistair [EMAIL PROTECTED]:
  Also, in Sqlite 3.4, they introduced new functions for incremental
  reading / writing of Blobs. I could use them in the future.

 Seems reasonable. I recall Oleg saying something privately a while ago
 about an API for large objects. He may have some ideas for this.

A good idea could be to do the marshalling / unmarshalling of Blob as
CStringLen. It can then be used to construct PackedStrings and
ByteStrings in O(1), or doing some custom computations with it. A
CStringLen, even if contains Ptr CChar, can easily be converted to any
pointer type.

Another idea could be using custom bind function for blobs, but the
first solution is surely easier.

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


Re: [Haskell-cafe] Handling custom types in Takusen

2007-07-27 Thread Salvatore Insalaco
2007/7/27, Bayley, Alistair [EMAIL PROTECTED]:
 It was my intention to do it the other way around: marshall blob to Ptr
 (), and then you can cast this to a Ptr CChar. Obviously you'd need to
 retain the size information, so a blob basically becomes a (Ptr (), Int)
 pair, just like a CStringLen...

 At least this way you've got a type which says explicitly this thing is
 a blob, and then if you know better, i.e. it's really a CString, you
 can cast it.

You're right, I'll work in this direction. Eventually I will add also
the CStringLen marshalling, as it is a pretty common case (BS, FPS,
PS) and it could be handy.

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


[Haskell-cafe] Re: Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Dave Bayer
Neil Mitchell ndmitchell at gmail.com writes:

 then lookup, instead of just  as the else clause.

Thanks, all. After digesting what was on this thread as I woke up this
morning, I ended up writing something rather close to this.

I have a reusable wrapper around System.Console.GetOpt that adds

 type Opt a = (a,String)
 
 noArg :: a - ArgDescr (Opt a)
 noArg x = NoArg (x,)
 
 reqArg :: a - String - ArgDescr (Opt a)
 reqArg x s = ReqArg f s
 where f y = (x,y)
 
 optArg :: a - String - ArgDescr (Opt a)
 optArg x s = OptArg f s
 where f (Just y) = (x,y)
   f Nothing  = (x,)
 
 isOption :: Eq a = a - [Opt a] - Bool
 isOption opt assoc =  case lookup opt assoc of
 Nothing - False
 Just _  - True
 
 getOption :: Eq a = a - [Opt a] - String
 getOption opt assoc = case lookup opt assoc of
 Nothing - 
 Just s  - s

Then in a project-specific module I write

 data Flag
 = Filter
 | DateFormat
 | DocStart
 | DocEnd
 | ForceStyle
 | Help
 deriving (Eq)
 
 defaults :: [Opt Flag]
 defaults =
 [ (Filter, Markdown.pl)
 , (DateFormat, %B %e, %Y)
 , (DocStart,   ^\\s*{-\\s*$)
 , (DocEnd, ^\\s*-}\\s*$)
 ]
 
 flags :: [OptDescr (Opt Flag)]
 flags =
 [ Option ['s'] [style]  (noArg ForceStyle)
 Overwrite existing style.css
 , Option ['m'] [markup] (reqArg Filter path)
 Path to Markdown-style markup filter
 , Option ['d'] [date]   (reqArg DateFormat format)
 Unix-style modification date format
 , Option ['a'] [start]  (reqArg DocStart string)
 Documentation start string
 , Option ['b'] [end](reqArg DocEnd string)
 Documentation end string
 , Option ['h'] [help]   (noArg Help)
 Print this help message
 ]

which looks almost like the sample code I started with. Reading quickly,
one might miss the case change from `NoArg` to `noArg`, etc.

This is simple, and it works, with less option-specific boilerplate. One
could imagine generating `flags` automatically from an extension of
`defaults`, but I'm content to move on.

The relevant code is at

http://www.math.columbia.edu/~bayer/Haskell/Annote/GetOpt.html
http://www.math.columbia.edu/~bayer/Haskell/Annote/Flags.html
http://www.math.columbia.edu/~bayer/Haskell/Annote/Main.html


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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-27 Thread Jon Fairbairn
ChrisK [EMAIL PROTECTED] writes:

 Jon Fairbairn wrote:
  I currently only get f :: [t] - something, so if I later
  discover that I need to change the input representation to
  be more efficient than lists, I have to rewrite f. Wouldn't
  it be so much nicer if I could simply add a declaration
 
  f:: Stream s = s t - something
  and get a function that works on anything in the Stream
  class?
  The core of the idea would be to allow classes to include
  constructors (and associated destructors) so the definition
  of Stream would include something for : and [] and their
  inverses, though I've no real idea of the details; can
  anyone come up with a plan?
 
 I had been avoiding adding my two cents, but I must object to this.
 
 Because this is starting to sound like one of the
 maddening things about C++.
 
 Namely, the automatic implicit casting conversions of
 classes via their single argument constructors.

Unfortunately I'm not sufficiently familiar with C++ to know
what this means. Perhaps you could clarify?

Despite the obvious interpretation of my message (ahem), I'm
not advocating much that's automatic. In the case of lists I
was imagining that they would be the default for Streams in
much the same way that Integer is the default for Num.  I'd
be happy to discard that part of the idea (though I'd expect
howls of protest from those who want lists to be ruling
class citizens).

 What if the 'f' in the quoted message above is itself part
 of a type class. Then one has to decide which instance 'f'
 is being called and what constructors/destructors are being
 called to view the 's t' parameter as the correct concrete
 type.  That way lies madness.

Again, I think the difficulty here is a discrepancy between
the interpretation of what I wrote and what I intended to
mean :-), viz that classes could (in addition to their usual
functions) define constructor/deconstructor pairs that would
be used in desugaring pattern matching.  I didn't mean that
constructors of the same name could appear both in classes
and in data declarations.  So if one had something like

class Stream s where
   Cons:: a - s a - s a
   Nil:: s a
   Snoc:: s a - a - s a
   ...

   {- an instance definition for Stream would have to
   somehow give both construction and deconstruction
   functions for Cons and Nil -}

then a definition of the form 

f Nil = ...
f (Cons h t) = ...

would be unambiguously f:: Stream s = s a - ...  (in the
absence of defaulting). There are issues about checking
coverage of cases, but I don't think that's the problem you
were raising?

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-27 Thread Dan Licata
On Jul26, Stefan O'Rear wrote:
  So, this syntax affects a lot of code, existing or otherwise, that
  doesn't use view patterns, which is something we're trying to avoid.
 
 Eh?  I *think* the typing rules are the same for the no-view case.  If
 the auto-deriving hack isn't implemented, you only need a
 deriving(View), otherwise there should be no change at all...

Assuming you don't have the functional dependency: affects in the
sense that any code you write has a generalized type, so you have to
explain view patterns to beginners right out of the gate, etc.  If you
write 

length [] = []
length (h : t) = 1 + length t

we don't want to have to explain to beginners why it has type

length :: forall a,b,c. View a [b] - a - Num c

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


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-27 Thread Dan Licata
On Jul26, apfelmus wrote:
 Yes, the types of the patterns don't unify. But each one is a
 specialization of the argument type. Note that the type signature is
 
   bar :: (forall a . ViewInt a = a) - String
 
 which is very different from
 
   bar :: forall a . ViewInt a = a - String
 
 Without the extension, we would write  bar  as follows
 
   bar :: (forall a . ViewInt a = a) - String
   bar x = let xNat = x :: Nat in
  case xNat of
Zero - ...
_- let xListBool = x :: [Bool] in
   case xListBool of
  True:xs - ...
 
 In other words, we can specialize the polymorphic argument to each
 pattern type and each equation may match successfully.

Oh, I understand what you're saying now.  Thanks for clarifying!
 
-Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-27 Thread Conor McBride

Me:
  In the dependently typed setting, it's often the case that the
  with-scrutinee is an expression of interest precisely because it
  occurs
  in the *type* of the function being defined. Correspondingly, an
  Epigram implementation should (and the Agda 2 implementation now  
does)

  abstract occurrences of the expression from the type.

Dan:
 Oh, I see: you use 'with' as a heuristic for guessing the motive  
of the

 inductive family elim.  How do you pick which occurrences of the
 with-scrutinee to refine, and which to leave as a reference to the
 original variable?  You don't always want to refine all of them,  
do you?


There are two components to this process, and they're quite separable.
Let's have an example (in fantasy dependent Haskell), for safe lookup.

defined :: Key - [(Key, Val)] - Bool
defined k []   = False
defined k ((k', _) : kvs)  = k == k' || defined k kvs

data Check :: Bool - * where
  OK :: Check True

lookup :: (k :: Key; kvs :: [(Key, Val)]) - Check (defined k kvs) -  
Val

lookup k []  !!  -- !! refutes Check False; no rhs
{-before-}
lookup k ((k', v) : kvs) p  with k == k'
{-after-}
lookup k ((k', v) : kvs) OK| True= v
lookup k ((k', v) : kvs) p'| False   = lookup k kvs p'

Left-hand sides must refine a 'problem', initially

  lookup k kvs p  where
k :: Key; kvs :: [(Key, Value)]; p :: Check (defined k kvs)

Now, {-before-} the with, we have patterns refining the problem

  lookup k ((k', v) : kvs) p  where
k, k' :: Key
v :: Val
kvs :: [(Key, Val)]
p :: Check (k == k' || defined k kvs)

The job of with is only to generate the problem which the lines in its
block must refine. We introduce a new variable, abstracting all
occurrences of the scrutinee. In this case, we get the new problem
{-after-}.

  lookup k ((k', v) : kvs) p | b  where
k, k' :: Key
v :: Val
kvs :: [(Key, Val)]
b :: Bool
p :: Check (b || defined k kvs)

All that's happened is the abstraction of (k == k'): no matching, no
mucking about with eliminators and motives. Now, when it comes to
checking the following lines, we're doing the same job to check
dependent patterns (translating to dependent case analysis, with
whatever machinery is necessary) refining the new problem. Now,
once b is matched with True or False, the type of p computes to
something useful.

So there's no real guesswork here. Yes, it's true that the choice
to abstract all occurrences of the scrutinee is arbitrary, but all
or nothing are the only options which make sense without a more
explicit mechanism to pick the occurrences you want. Such a
mechanism is readily conceivable: at worst, you just introduce a
helper function with an argument for the value of the scrutinee and
write its type explicitly.

I guess it's a bit weird having more structure to the left-hand
side. The approach here is to allow the shifting of the problem,
rather than to extend the language of patterns. It's a much
better fit to our needs. Would it also suit Haskell?

Cheers

Conor

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


[Haskell-cafe] Re: Re: Avoiding boilerplate retrieving GetOpt

2007-07-27 Thread Eric Kow
 For starters, you could squish these down into something like

  flagToString :: Flag - Maybe String
  flagToString (Filter s) = Just s
  flagToString (DateFormat s) = Just s
  ...
  flagToString _ = Nothing

What am I saying?! This wouldn't work!  Sorry for the noise.

-- 
Eric Kow http://www.loria.fr/~kow
PGP Key ID: 08AC04F9 Merci de corriger mon français.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Ray tracer language comparison

2007-07-27 Thread Jon Harrop

I've added four progressively optimized implementations of the Haskell ray 
tracer to the language comparison:

  http://www.ffconsultancy.com/languages/ray_tracer/

Only the first is lazy and I haven't mentioned them in the discussion yet.

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Handling custom types in Takusen

2007-07-27 Thread Salvatore Insalaco
2007/7/27, Bayley, Alistair [EMAIL PROTECTED]:
 BTW, do you really need to marshall PackedStrings to blobs? The Sqlite
 library uses CStrings, and I assume that CString to PackedString
 marshaling is fairly efficient, so that would seem to be a better
 choice. (I have no experience of PackedStrings, so there might be good
 reasons to prefer blobs, and I'd like to know what they are.)

The main reason is that I'm working on a Sqlite back-end for Darcs,
that will be used to store file contents.
I think to choose Takusen as back-end library mainly because it has
the blob functions of Sqlite already mapped.

In Darcs PackedStrings are used to store file contents in memory. I
don't think that it would be very efficient to store files of
megabytes in a text column (there could be encoding problems too).

Also, in Sqlite 3.4, they introduced new functions for incremental
reading / writing of Blobs. I could use them in the future.

Thank you a lot for helping! I'll surely send you the patches, even if
the PackedString support will be a little Darcs-specific (I don't
think that requiring it for compiling Takusen is a good idea).

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


RE: [Haskell-cafe] Handling custom types in Takusen

2007-07-27 Thread Bayley, Alistair
 From: Salvatore Insalaco [mailto:[EMAIL PROTECTED] 
 
 2007/7/27, Bayley, Alistair [EMAIL PROTECTED]:
   Also, in Sqlite 3.4, they introduced new functions for incremental
   reading / writing of Blobs. I could use them in the future.
 
  Seems reasonable. I recall Oleg saying something privately 
 a while ago
  about an API for large objects. He may have some ideas for this.
 
 A good idea could be to do the marshalling / unmarshalling of Blob as
 CStringLen. It can then be used to construct PackedStrings and
 ByteStrings in O(1), or doing some custom computations with it. A
 CStringLen, even if contains Ptr CChar, can easily be converted to any
 pointer type.
 
 Another idea could be using custom bind function for blobs, but the
 first solution is surely easier.

It was my intention to do it the other way around: marshall blob to Ptr
(), and then you can cast this to a Ptr CChar. Obviously you'd need to
retain the size information, so a blob basically becomes a (Ptr (), Int)
pair, just like a CStringLen...

At least this way you've got a type which says explicitly this thing is
a blob, and then if you know better, i.e. it's really a CString, you
can cast it.

Actually, it wouldn't cost much to have both marshalling functions in
the low-level API, even if they both call the same Sqlite blob retrieval
function.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-27 Thread Jonathan Cast
On Friday 27 July 2007, Jon Fairbairn wrote:
 ChrisK [EMAIL PROTECTED] writes:
  Jon Fairbairn wrote:
   I currently only get f :: [t] - something, so if I later
   discover that I need to change the input representation to
   be more efficient than lists, I have to rewrite f. Wouldn't
   it be so much nicer if I could simply add a declaration
  
   f:: Stream s = s t - something
  
   and get a function that works on anything in the Stream
   class?
   The core of the idea would be to allow classes to include
   constructors (and associated destructors) so the definition
   of Stream would include something for : and [] and their
   inverses, though I've no real idea of the details; can
   anyone come up with a plan?
 
  I had been avoiding adding my two cents, but I must object to this.
 
  Because this is starting to sound like one of the
  maddening things about C++.
 
  Namely, the automatic implicit casting conversions of
  classes via their single argument constructors.

 Unfortunately I'm not sufficiently familiar with C++ to know
 what this means. Perhaps you could clarify?

Somebody noticed that, in C, you could mix integers and floats (almost) 
freely, and in Classic C, you could mix pointers and integers freely, and 
thought this was /such/ a wonderful idea that C++ has special syntax to 
declare the conversion functions allowing you to, say, mix pointers and 
pointer-like classes freely, or to mix char*s and strings freely, etc.  It's 
what makes

templatealpha
class AutoPtralpha{
  alpha *ptr;
public:
  explicit AutoPtr(){
ptr = new alpha; }
  AutoPtr(alpha *p){
ptr = p; }
  ~AutoPtr(){
delete ptr; }
  alpha operator *(){
return *ptr; }
  operator (alpha*)(){
return ptr; }};

templatealpha
external void swap(alpha *, alpha *);

...

AutoPtrint ptr1;
AutoPtrint ptr2;

...

swap (ptr1, ptr2);

Type-check.

 Despite the obvious interpretation of my message (ahem), I'm
 not advocating much that's automatic. In the case of lists I
 was imagining that they would be the default for Streams in
 much the same way that Integer is the default for Num.  I'd
 be happy to discard that part of the idea (though I'd expect
 howls of protest from those who want lists to be ruling
 class citizens).

  What if the 'f' in the quoted message above is itself part
  of a type class. Then one has to decide which instance 'f'
  is being called and what constructors/destructors are being
  called to view the 's t' parameter as the correct concrete
  type.  That way lies madness.

 Again, I think the difficulty here is a discrepancy between
 the interpretation of what I wrote and what I intended to
 mean :-), viz that classes could (in addition to their usual
 functions) define constructor/deconstructor pairs that would
 be used in desugaring pattern matching.  I didn't mean that
 constructors of the same name could appear both in classes
 and in data declarations.  So if one had something like

 class Stream s where
Cons:: a - s a - s a
Nil:: s a
Snoc:: s a - a - s a
...

{- an instance definition for Stream would have to
somehow give both construction and deconstruction
functions for Cons and Nil -}

 then a definition of the form

 f Nil = ...
 f (Cons h t) = ...

 would be unambiguously f:: Stream s = s a - ...  (in the
 absence of defaulting). There are issues about checking
 coverage of cases, but I don't think that's the problem you
 were raising?



-- 
Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs


pgp2HFuJ8WyTQ.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request forfeedback

2007-07-27 Thread Jacques Carette
Others have already pointed this out, but it is worth saying again: 
Maybe is not the only monadic effect which makes sense during 
pattern-matching.  Wolfram Kahl and I have explored some of these things 
as part of the Pattern Matching Calculus,

http://sqrl.mcmaster.ca/~kahl/PMC/
[If you want to jump to the most recent, most complete version, see
http://www.cas.mcmaster.ca/~kahl/Publications/TR/Kahl-Carette-Ji-2006b/]

Various other monads can be used for pattern-matching-effects.  While 
Maybe is quite classical, List and LogicT give extremely useful 
alternatives.


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


[Haskell-cafe] Re: Handling custom types in Takusen

2007-07-27 Thread Benjamin Franksen
Salvatore Insalaco wrote:
 I noticed that in Takusen there're just two instances to implement to
 make any Haskell type db-serializable: DBBind / SqliteBind for
 serialization and DBType for deserialization.

FWIW, I have two patches lying around (attached) that I wanted to send to
the Takusen maintainers anyway. They (the patches) implement (only)
instance DBType Data.ByteString for Oracle and Sqlite backends. They are
rudimentarily tested (hey, seems to work!), anyway a review might be in
order because I am not sure I understand the internals good enough -- for
all I know I might have introduced space leaks or whatnot.

Cheers
Ben
New patches:

[added ByteString support to Database/Oracle
[EMAIL PROTECTED] {
hunk ./Database/Oracle/Enumerator.lhs 41
+ import qualified Data.ByteString.Char8 as B

hunk ./Database/Oracle/Enumerator.lhs 948
+ bufferToByteString :: ColumnBuffer - IO (Maybe B.ByteString)

+ bufferToByteString buffer = OCI.bufferToByteString (undefined, 
colBufBufferFPtr buffer, colBufNullFPtr buffer, colBufSizeFPtr buffer)

+

hunk ./Database/Oracle/Enumerator.lhs 1010
+ instance DBType (Maybe B.ByteString) Query ColumnBuffer where

+   allocBufferFor _ q n = allocBuffer q (16000, oci_SQLT_CHR) n

+   fetchCol q buffer = bufferToByteString buffer

+

hunk ./Database/Oracle/OCIFunctions.lhs 39
+ import qualified Data.ByteString.Base as B

hunk ./Database/Oracle/OCIFunctions.lhs 676
+

+ bufferToByteString :: ColumnInfo - IO (Maybe B.ByteString)

+ bufferToByteString (_, bufFPtr, nullFPtr, sizeFPtr) =

+   withForeignPtr nullFPtr $ \nullIndPtr - do

+ nullInd - liftM cShort2Int (peek nullIndPtr)

+ if (nullInd == -1)  -- -1 == null, 0 == value

+   then return Nothing

+   else do

+ -- Given a column buffer, extract a string of variable length

+ withForeignPtr bufFPtr $ \bufferPtr -

+   withForeignPtr sizeFPtr $ \retSizePtr - do

+ retsize - liftM cUShort2Int (peek retSizePtr)

+ --create :: Int - (Ptr Word8 - IO ()) - IO ByteString

+ val - B.create retsize (\p - copyBytes (castPtr p) bufferPtr 
retsize)

+ return (Just val)

}

[added ByteString support to Database/Sqlite
Ben Franksen [EMAIL PROTECTED]**20070714230837] {
hunk ./Database/Sqlite/Enumerator.lhs 38
+ import qualified Data.ByteString.Char8 as B

hunk ./Database/Sqlite/Enumerator.lhs 366
+ bufferToByteString query buffer =

+   DBAPI.colValByteString (stmtHandle (queryStmt query)) (colPos buffer)

+

hunk ./Database/Sqlite/Enumerator.lhs 414
+ instance DBType (Maybe B.ByteString) Query ColumnBuffer where

+   allocBufferFor _ q n = allocBuffer q n

+   fetchCol q buffer = bufferToByteString q buffer

+

hunk ./Database/Sqlite/SqliteFunctions.lhs 22
+ import qualified Data.ByteString.Char8 as B

hunk ./Database/Sqlite/SqliteFunctions.lhs 278
+

+ colValByteString :: StmtHandle - Int - IO (Maybe B.ByteString)

+ colValByteString stmt colnum = do

+   cstrptr - sqliteColumnText stmt (fromIntegral (colnum - 1))

+   if cstrptr == nullPtr

+ then return Nothing

+ else do

+   str - B.copyCString cstrptr

+   return (Just str)

}

Context:

[added Functor and MonadFix instances to DBM
Ben Franksen [EMAIL PROTECTED]**20070714112112] 
[TAG 0.6
[EMAIL PROTECTED] 
Patch bundle hash:
3bd78e14633d172cbabf4fd716fc0bcf3b32fa8c
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request?for?feedback

2007-07-27 Thread David Roundy
On Fri, Jul 27, 2007 at 09:02:42AM -0500, Jonathan Cast wrote:
 On Friday 27 July 2007, Jon Fairbairn wrote:
  ChrisK [EMAIL PROTECTED] writes:
   Because this is starting to sound like one of the
   maddening things about C++.
  
   Namely, the automatic implicit casting conversions of
   classes via their single argument constructors.
 
  Unfortunately I'm not sufficiently familiar with C++ to know
  what this means. Perhaps you could clarify?
 
 Somebody noticed that, in C, you could mix integers and floats (almost) 
 freely, and in Classic C, you could mix pointers and integers freely, and 
 thought this was /such/ a wonderful idea that C++ has special syntax to 
 declare the conversion functions allowing you to, say, mix pointers and 
 pointer-like classes freely, or to mix char*s and strings freely, etc.  It's 
 what makes

To give a somewhat more mundane example if you define a class Array

class Array {
public:
  Array(int); // ... construct a new array of specified length
  ...
}

Then if you make the mistake of passing an integer constant to a function
that expects an Array, C++ will happily construct a new Array of that size
and pass that to the function.

Even more exciting when you use overloading: if you define multiplication
between two Arrays, then if you accidentally try to multiply an Array by an
integer constant (thinking it'll be a scalar multiply), then a new Array of
that size will be constructed and multiplied--almost certainly resulting in
a runtime error (mismatched Array sizes), but certainly not what you want.

The solution is to add explicit to the constructor for all single-argument
constructors (except perhaps occasionally when you actually want explicit
construction of objects).

The reasoning behind this, of course, is to allow nice interactions of
home-made classes such as complex numbers, or string classes (which you
might want to be automatically constructed from string constants).
-- 
David Roundy
Department of Physics
Oregon State University


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


Re: Re : [Haskell-cafe] Indentation woes

2007-07-27 Thread Brandon Michael Moore
On Thu, Jul 26, 2007 at 05:34:32PM -0400, anon wrote:
 2007/7/26, Stefan O'Rear [EMAIL PROTECTED]:
 As for why, it's just a matter of Haskell Committee taste.  Nothing
 too deep, just an arbitrary set of rules.
 That's not much of an explanation, is it? I imagine someone must have
 given the matter some thought before describing the layout rule in
 great details in the language report. Perhaps there was a perfectly
 good reason to preclude this kind of code, but I'm afraid I do need a
 reason if I am to understand why.

Part of the reason is that the layout rule is supposed to be somewhat
independent of the rest of the grammar. It's described as a simple
preprocessing state that adds block delimiters { ; } just recongizing
a few keywords that open blocks, and otherwise looking at the indentation
of the first non-whitespace character on lines.

You can allow the syntaxes where something is no less indented than it's
containing block by allowing some optional semicolons in the grammar.
GHC keeps it's parser in compiler/parser/Parser.y.pp It's a Happy
grammar file, it shouldn't be hard to make your change and see how
you like it. I think the gdrh nonterminal is the one you want to change,
add another production that allows ';' '|' quals '=' exp

Have fun

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


[Haskell-cafe] Re: Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Eric Y. Kow
To anyone who followed up on this thread (hi!).  I have posted the
GetOpt-summary part of my message on the wiki:

   http://www.haskell.org/haskellwiki/GetOpt

Please update it with the relevant parts of your followups, and correct
any silliness.  Haven't had the time to look, but I'm particularly
interested in what Johnathan suggested because (at a glance), it seems
far less clumsy than my solution #4.  As usual, don't hesitate to remove
things from this page, rename it, etc.

-- 
Eric Kow http://www.loria.fr/~kow
PGP Key ID: 08AC04F9 Merci de corriger mon français.


pgpBQ884kv2Eb.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request?for?feedback

2007-07-27 Thread Aaron Denney
On 2007-07-27, David Roundy [EMAIL PROTECTED] wrote:
 The solution is to add explicit to the constructor for all single-argument
 constructors (except perhaps occasionally when you actually want explicit
 construction of objects).

 The reasoning behind this, of course, is to allow nice interactions of
 home-made classes such as complex numbers, or string classes (which you
 might want to be automatically constructed from string constants).

I'd have thought that adding an implicit keyword would make more
sense, and only do conversions then.  But I forget, C++.

-- 
Aaron Denney
--

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


[Haskell-cafe] Memory profiler

2007-07-27 Thread Jon Harrop

Is there a memory profiler for Haskell?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memory profiler

2007-07-27 Thread Stefan O'Rear
On Sat, Jul 28, 2007 at 12:11:31AM +0100, Jon Harrop wrote:
 Is there a memory profiler for Haskell?

Yes.  GHC, NHC and HBC all have integrated heap profilers.

ghc --make -prof -auto-all ...
./MyProgram +RTS -hc -RTS
./MyProgram +RTS -hm -RTS
./MyProgram +RTS -hd -RTS
./MyProgram +RTS -hy -RTS
...

http://haskell.org/ghc/dist/current/docs/users_guide/prof-heap.html

Stefan


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


[Haskell-cafe] Using GADTs

2007-07-27 Thread Matthew Pocock
Hi,

I'm trying to get to grips with GADTs, and my first attempt was to convert a 
simple logic language into negative normal form, while attempting to push the 
knowledge about what consitutes negative normal form into the types. My code 
is below.

I'm not entirely happy with it, and would appreciate any feedback. The rules 
are that in nnf, only named concepts, the concept Top and the concept Bottom 
can be negated. So, I've added three NNFNegation_* constructors capturing 
these legal cases. Is there a way to use one constructor, that is allowed 
to 'range over' these three cases and none of the others?

I've ended up producing two data types, one for the general form and one for 
the nnf. Actually, the constraint on what constitutes nnf is fairly obvious - 
no complex terms are negated. Is there a way to use just the one data type 
but to describe two levels of constraints - one for the general case, and one 
for the nnf case? Or is the whole point that you capture each set of 
constraints in a different data type?

Thanks,

Matthe


data Named
data Equal
data Conjunction
data Disjunction
data Negation
data Existential
data Universal
data Top
data Bottom

data Concept t where
  CNamed   :: String - Concept Named
  CEqual   :: Concept a - Concept b - Concept Equal
  CConjunction :: Concept a - Concept b - Concept Conjunction
  CDisjunction :: Concept a - Concept b - Concept Disjunction
  CNegation:: Concept a - Concept Negation
  CExistential :: Role Named - Concept Existential
  CUniversal   :: Role Named - Concept Universal
  CTop :: Concept Top
  CBottom  :: Concept Bottom

data NNFConcept t where
  NNFCNamed   :: String - NNFConcept Named
  NNFCEqual   :: NNFConcept a - NNFConcept b - NNFConcept Equal
  NNFCConjunction :: NNFConcept a - NNFConcept b - NNFConcept Conjunction
  NNFCDisjunction :: NNFConcept a - NNFConcept b - NNFConcept Disjunction
  NNFCExistential :: Role Named - NNFConcept Existential
  NNFCUniversal   :: Role Named - NNFConcept Universal
  NNFCTop :: NNFConcept Top
  NNFCBottom  :: NNFConcept Bottom
  
  NNFCNegation_N  :: NNFConcept Named  - Concept Negation
  NNFCNegation_T  :: NNFConcept Top- Concept Negation
  NNFCNegation_B  :: NNFConcept Bottom - Concept Negation

data Role t where
  RNamed :: String - RNamed Named

-- terms not prefixed with a negation are already in nnf
nnf :: Concept t - NNFConcept u
nnf CNamed   name = NNFCNamed name
nnf CEqual   lhs  rhs = NNFConcept  (nnf lhs) (nnf rhs)
nnf CConjunction lhs  rhs = NNFCConjunction (nnf lhs) (nnf rhs)
nnf CDijunction  lhs  rhs = NNFCDisjunction (nnf lhs) (nnf rhs)
nnf CExistential rc   = NNFCExistential r (nnf c)
nnf CUniversal   rc   = NNFCUniversal   r (nnf c)

-- if negated, we must look at the term and then do The Right Thing(tm)
nnf CNegation (CNamed name)  = NNFCNegation_N  NNFCNamed name
nnf CNegation (CEqual lhs rhs)   = NNFCEqual   (nnf $ CNegation lhs) 
(nnf $ CNegation rhs)
nnf CNegation (CConjunction lhs rhs) = NNFCDisjunction (nnf $ CNegation lhs) 
(nnf $ CNegation rhs)
nnf CNegation (CDisjunction lhs rhs) = NNFCConjunction (nnf $ CNegation lhs) 
(nnf $ CNegation rhs)
nnf CNegation (CNegation c)  = nnf c
nnf CNegation (CExistential r c) = NNFCUniversal   r 
(nnf $ CNegation c)
nnf CNegation (CUniveralr c) = NNFCExistential r 
(nnf $ CNegation c)
nnf CNegation CTop   = NNFCNegation_T NNFCTop
nnf CNegation CBottom= NNFCNegation_B NNFCBottom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space usage and CSE in Haskell

2007-07-27 Thread Melissa O'Neill

Bertram Felgenhauer wrote two wonderful implementations of power_list:

  power_list :: [a] - [[a]]
  power_list [] = [[]]
  power_list (x:xs) = add_x (assert_first_empty $ power_list xs) x
 where assert_first_empty ~([]:xs) = []:xs
   add_x [] _ = []
   add_x (y:ys) x = y : (x:y) : add_x ys x

It's safe to replace the ~([]:xs) by ~(_:xs) - this should result  
in slightly more efficient code (but I did no timings).


With GHC, it seems to make no observable difference.

Finally for lovers of oneliners, here's the same code with foldr,  
slightly obscured by using = for concatMap:


  power_list :: [a] - [[a]]
  power_list = foldr (\x ~(_:xs) - []:xs = \ys - [ys, x:ys]) [[]]


I loved how short and sweet this version is, but sadly with GHC it's  
noticeably slower than Bertram's first, more directly coded, version  
(1.32 seconds vs 0.55 seconds for power_list [1..24]).


The two-line variant below is just over 25% faster than the above  
oneliner under GHC, but at 1.04 seconds, it's still bested by the  
explicit version:


  power_list :: [a] - [[a]]
  power_list [] = [[]]
  power_list (x:xs) = [] : tail [y | ps - power_list xs, y - [ps,  
x:ps]]


Anyway, we're now far from our original topic, but thanks to Bertram,  
we can see that power_list can be coded in a way that is memory  
efficient, lazy-list friendly, and (relatively) easy to read.


Best Regards,

Melissa.

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


[Haskell-cafe] Takusen and large PostgreSQL blobs [was: Handling custom types in Takusen]

2007-07-27 Thread oleg

I have been using Takusen with PostgreSQL to store and retrieve
hundreds of multi-megabyte binary objects. A client may request
literally hundred of such objects in one request; the Haskell
(FastCGI) application server will send these objects in one multi-part
message. The handling of the entire request is done in *constant* and
small memory, at low latency and at the rate that is limited by
client's network connection. The server handles hundreds of such
requests without allocating memory: the Haskell server uses only one
16KB buffer for all of its I/O. Incidentally, with the exception of
occasional existential and extended pattern guards, all the server
code is in Haskell98.

I have been using LO objects of PostgreSQL. That is not the only
design choice: an alternative is to create a table where each row
holds a chunk (e.g., 16K) of data as a byte array. The row will have
two more columns: the blob id and the chunk ordinal counter. This
design lets one incrementally write binary data (using COPYIN
technique) and read data (using COPYOUT or the regular SQL
queries). The COPYIN feature lets us write to the database in
user-defined chunks. Alas, the converse, COPYOUT, can read only whole
rows, which precludes storing all of the data in one row. If we
segment the data in chunks spread across several rows, we regain
incrementality. I have a hunch this method may be preferable, although
I have not tried it. The drawback of LO objects is the need for
frequent vacuuming, which may take really a while if many large
objects are being created and deleted.

The blob interface is designed to permit incremental reading and
writing blobs. In fact, the server never stores the whole blob in
memory. 

Enclosed are the implementations of store_lo and consume_lo
functions. They rely on the notions of `generalized' input and output
ports and the generalized copier. I've been meaning to describe them
properly but don't seem to get around to it. I could refer to the
comments in the file
http://okmij.org/ftp/Haskell/NewerCGI.hs
Frequently mentioned EMonadIO is a class of monad that permit both i/o
operations and throwing _and_ catching of arbitrary errors. Most of
the transformations of IO are in that class. EMonadIO lets me write
gthrow, gcatch, ghandle, gbracket, etc. without even thinking in which
monad I currently am.



-- Read data from a LO (a kind of PostgreSQL blobs). A blob is identified
-- by its Oid. We determine the size of the blob, create a generalized
-- input port for reading from the blob, and pass the size and the
-- port to the user function. The function will probably use BCopy
-- to copy data from the blob to somewhere else. The function should
-- not store the generalized input port anywhere as the port can't be
-- used after the function returns. We could have enforced that with a
-- marker and Typeable, as we do in Takusen.
-- This function must be invoked in a transaction (it would cause a
-- database error otherwise).
-- We don't bracket the call to the user function as any exceptions
-- are fatal anyway.
consume_lo :: EMonadIO m = Connection - Oid -
  (Int - Input - m a) - m a
consume_lo (Connection db) oid f = 
   do
lofd - liftIO $ check_pos lo_open $ flo_open db oid eINV_READ
  -- get the size of LO by seeking to the end, and coming back
size - liftIO $ check_pos lo_lseek $ flo_lseek db lofd 0 eSEEK_END
liftIO $ check_pos lo_lseek $ flo_lseek db lofd 0 eSEEK_SET
let inp = Input (\ptr len - 
 liftIO . liftM fromIntegral . check_pos lo_read $ 
 flo_read db lofd ptr (fromIntegral len))
r - f (fromIntegral size) inp
liftIO $ check_pos lo_close $ flo_close db lofd
return r
  `gcatch` \e - print_exc e  liftIO (closeDb db)  gthrow e
 where
 check_pos str a = a = \r - if r = 0 then return r else throwPG r str


-- Write data to a LO (a kind of PostgreSQL blobs). A blob is identified
-- by its Oid. We create a generalized output port for writing to the blob,
-- and pass it to the user function. The function will probably use BCopy
-- to copy data to the blob from somewhere else. The function should
-- not store the generalized output port anywhere as the port can't be
-- used after the function returns. We could have enforced that with a
-- marker and Typeable, as we do in Takusen.
-- This function must be invoked in a transaction (it would cause a
-- database error otherwise).
-- We don't bracket the call to the user function as any exceptions
-- are fatal anyway.
store_lo :: EMonadIO m = Connection - Oid - (Output - m a) - m a
store_lo (Connection db) oid f = 
   do
lofd - liftIO $ check_pos lo_open $ flo_open db oid eINV_WRITE
let outp = Output (\ptr len - 
 liftIO (check_size len = check_pos lo_write
 (flo_write db lofd ptr (fromIntegral len
r - f outp
liftIO $ check_pos lo_close $ flo_close db lofd
return r
  `gcatch` \e - print_exc e  liftIO (closeDb db)  gthrow e