Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-20 Thread Alfonso Acosta
OK I'll include the module after I change the things mentioned.

BTW, I finally have an initial version of the parameterized-data package:

Darcs repository:

http://code.haskell.org/parameterized-data

Haddock documentation:

http://code.haskell.org/~fons/parameterized-data/doc/

Any comments/suggestions would be appreciated.

To fix the problem of the vector constructor I included a Template
Haskell variant. It is quite simple to use:

$ ghci -XTemplateHaskell
Prelude :m +Data.Param
Prelude Data.Param $(vectorTH [1 :: Int, 2, 3, 4])
Prelude Data.Param :t $(vectorTH [1 :: Int, 2, 3, 4])
(vectorTH [1 :: Int, 2, 3, 4]) :: (Num t) = FSVec Data.TypeLevel.Num.Reps.D4 t

Note that the size parameter (type-level decimal numeral) is correct.

It would be nice to be able to use a Quasiquoter [1] (available in GHC
HEAD) to enable pattern matching and custom syntax to Vector literals.
However, I was bitten by a polymorphism problem when implementing it:
see [2] for details

[1] 
http://www.haskell.org/ghc/dist/current/docs/users_guide/template-haskell.html#th-quasiquotation
[2] http://www.haskell.org/pipermail/template-haskell/2008-February/000655.html

On Wed, Feb 20, 2008 at 2:26 AM, Wolfgang Jeltsch
[EMAIL PROTECTED] wrote:
 Am Mittwoch, 20. Februar 2008 00:39 schrieben Sie:

  Why are the value-level reflecting functionsimplemented as type-class
   methods? It makes the code more verbose and I don't see any advantage
   compared to simply defining a function per class. Let me show you an
   example:
  
   This is your implementation of Not:
  
   class (Boolean boolean, Boolean boolean') =
 Not boolean boolean' | boolean - boolean', boolean' - boolean
   where not :: boolean - boolean'
  
   instance Not False True where
   not _ = true
  
   instance Not True False where
   not _ = false
  
   This is how I would do it:
  
   class (Boolean boolean, Boolean boolean') =
 Not boolean boolean' | boolean - boolean', boolean' - boolean
   where
  
   instance Not False True
   instance Not True False
  
  not :: Not a b = a - b
  not = undefined

  Your definition of the not function uses the implementation detail that false
  and true are actually undefined.  My implementation of the not function also
  works if false and true are defined to be something different.  Of course,
  false and true are in the same library, so we know this implementation detail
  and could make use of it.


   Furthermore, why did you choose to use Boolean instead of simply Bool?

  To avoid a name clash.  Feel free to change this.

  Note that False and True don't cause a name clash since they live in a
  namespace different from the one Prelude's False and True live in.

   Cheers,
  
   Fons



  Best wishes,
  Wolfgang
  ___
  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] Doubting Haskell

2008-02-20 Thread Cale Gibbard
(I'm copying the list on this, since my reply contains a tutorial
which might be of use to other beginners.)

On 19/02/2008, Alan Carter [EMAIL PROTECTED] wrote:
 Hi Cale,

 On Feb 19, 2008 3:48 PM, Cale Gibbard [EMAIL PROTECTED] wrote:
  Just checking up, since you haven't replied on the list. Was my
  information useful? Did I miss any questions you might have had? If
  you'd like, I posted some examples of using catch here:

 Thanks for your enquiry! My experiment continues. I did put a progress
 report on the list - your examples together with a similar long an
 short pair got me over the file opening problem, and taught me some
 things about active whitespace :-) I couldn't get withFile working
 (says out of scope, maybe 'cos I'm ghc 6.6 on my Mac)

Make sure to put:

import System.IO

at the top of your source file, if you haven't been. This should
import everything documented here:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html

 but it turned out the line I was looking for (collapsed from the examples)
 was:

   text - readFile data.txt `catch` \_ - return 

 This ensures the program never loses control, crashing or becoming
 unpredictable by attempting to use an invalid resource, by yielding an
 empty String if for any reason the file read fails. Then an empty
 String makes it very quickly through parsing. I guess that's quite
 functiony :-)

 Amazing how easy once I knew how. Even stranger that I couldn't find a
 bread and butter example of it.

 Then I was going very quickly for a while. My file is dumped from a
 WordPress MySql table. Well formed lines have 4 tab separated fields
 (I'm using pipes for tabs here):

 line id | record id | property | value

 Line IDs are unique and don't matter. All lines with the same record
 ID give a value to a property in the same record, similar to this:

 1|1|name|arthur
 2|1|quest|seek holy grail
 3|1|colour|blue
 4|2|name|robin
 5|2|quest|run away
 6|2|colour|yellow

 Organizing that was a joy. It took minutes:

let cutUp = tail (filter (\fields - (length fields) == 4)
  (map (\x - split x '\t') (lines text)))

This should almost certainly be a function of text:

cutUp text = tail (filter (\fields - (length fields) == 4)
 (map (\x - split x '\t') (lines text)))

 I found a split on someone's blog (looking for a library tokenizer),
 but I can understand it just fine. I even get to chuck out ill-formed
 lines and remove the very first (which contains MySql column names) on
 the way through!

Sadly, there's no general library function for doing this. We have
words and lines (and words would work here, if your fields never have
spaces), but nobody's bothered to put anything more general for simple
splitting into the base libraries (though I'm sure there's plenty on
hackage -- MissingH has a Data.String.Utils module which contains
split and a bunch of others, for example). However, for anything more
complicated, there are also libraries like Parsec, which are generally
really effective, so I highly recommend looking at that at some point.

 I then made a record to put things in, and wrote some lines to play
 with it (these are the real property names):

 data Entry = Entry
   { occupation:: String
   , iEnjoyMyJob   :: Int
   , myJobIsWellDefined:: Int
   , myCoworkersAreCooperative :: Int
   , myWorkplaceIsStressful:: Int
   , myJobIsStressful  :: Int
   , moraleIsGoodWhereIWork:: Int
   , iGetFrustratedAtWork  :: Int
   }
 ...
   let e = Entry{occupation = , iEnjoyMyJob = 0}
   let f = e {occupation = alan}
   let g = f {iEnjoyMyJob = 47}
   putStrLn ((occupation g) ++   ++ (show (iEnjoyMyJob g)))

 Then I ran into another quagmire. I think I have to use Data.Map to
 build a collection of records keyed by record id, and fill them in by
 working through the list of 4 item lists called cutUp. As with the
 file opening problem I can find a few examples that convert a list of
 tuples to a Data.Map, one to one. I found a very complex example that
 convinced me a map from Int to a record is possible, but gave me no
 understanding of how to do it. I spent a while trying to use foldl
 before I decided it can't be appropriate (I need to pass more values).
 So I tried a couple of recursive functions, something like:

 type Entries = M.Map Int Entry
 ...
   let entries = loadEntries cutUp
 ...
 loadEntries :: [[String]] - Entries
 loadEntries [] = M.empty Entries
 loadEntries [x : xs] = loadEntry (loadEntries xs) x
-- Possible common beginner error here: [x:xs] means the list with one
element which is a list whose first element is x and whose tail is xs.
Your type signature and the type of cutUp seems to confirm that this
is the right type, but you don't seem to have a case to handle a
longer list of lists. If you want just a list with first entry x, and
with tail xs, that's just (x:xs). If you want to handle lists of 

Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-20 Thread Wolfgang Jeltsch
Am Mittwoch, 20. Februar 2008 09:20 schrieben Sie:
 OK I'll include the module after I change the things mentioned.

 BTW, I finally have an initial version of the parameterized-data package:

 Darcs repository:

 http://code.haskell.org/parameterized-data

 Haddock documentation:

 http://code.haskell.org/~fons/parameterized-data/doc/

 Any comments/suggestions would be appreciated.

Hello Fons,

why do you use the term vector?  I’d say that this term is more or less wrong 
for what this type is about.  The distinguishing property of vectors compared 
to lists is that there is addition and scalar multiplication for vectors.  
Being a list of fixed size is not so important for vectors, in fact, it’s 
completely unnecessary.  Real numbers are vectors, functions from real 
numbers to real numbers are vectors, matrixes are vectors—you just have to 
provide them with proper addition and scalar multiplication.  The data type 
you defined is a fixed size list.

 […]

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


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Henning Thielemann



Now, to help solve this problem, I wrote ListLike[2], providing a
set of typeclasses that make list operations generic.  I also provided
default instances of ListLike for:

 ListLike Data.ByteString.ByteString Word8
 ListLike Data.ByteString.Lazy.ByteString Word8
 ListLike [a] a
 (Integral i, Ix i) = ListLike (Array i e) e
 (Ord key, Eq val) = ListLike (Map key val) (key, val)


It's a multi-parameter type class, right? So it's difficult to push it to 
the core.



Now, the questions:

1) Does everyone agree with me that we have a problem here?


I agree.


2) Would it make sense to make ListLike, or something like it,
  part of the Haskell core?


Somehow yes. However since the 'base' package is constantly split into 
smaller parts, there is maybe no need to merge it somewhere, but introduce 
simply new package dependencies.



3) Would it make sense to base as much code as possible in the Haskell
  core areound ListLike definitions?  Here I think of functions such
  as lines and words, which make sense both on [Char] as well as
  ByteStrings.

4) We are missing one final useful type: a Word32-based ByteString.
  When working in the Unicode character set, a 32-bit character
  can indeed be useful, and I could see situations in which the
  performance benefit of a ByteString-like implementation could
  be useful combared to [Char].


StorableVector should fill this gap.
  http://code.haskell.org/~sjanssen/storablevector/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
Hi folks,

Before I started using Haskell, I used OCaml for a spell.  One of my
biggest annoyances with OCaml was that it had two list types: the
default list (strict), and a lazy list (known as a stream).

This led to all sorts of annoyances.  Libraries were always written to
work with one list or the other.  If you wanted to use two libraries,
one that assumed one list and the other that assumed another, you had
a difficult task ahead of you.

I am concerned that the same thing is happening in Haskell.  We know
have three common list-like types: the regular list, strict
ByteString, and lazy ByteString.

This has created some annoying situations.  For instance, a ByteString
is great for reading data fast, but Parsec doesn't work on
ByteStrings.  I am glad that someone wrote a Parsec equivolent that
does[1], which answers a real need.  But this means that all the
combinators in the hsemail library that implement standard RFC
conventions won't be usable in my ByteString code, for instance.

Similarly, we have another annoying situation relating to character
encodings:

 * The iconv library works only on lazy ByteStrings, and does not
   handle Strings or strict ByteStrings

 * The utf8-string library doesn't support UTF-16, doesn't require an
   external library, and works only on Strings -- no support for
   ByteStrings.

 * Data.Encoding.* is native haskell, supports UTF-*, but works only
   on ByteSting.Lazy again.

Now, to help solve this problem, I wrote ListLike[2], providing a
set of typeclasses that make list operations generic.  I also provided
default instances of ListLike for:

  ListLike Data.ByteString.ByteString Word8
  ListLike Data.ByteString.Lazy.ByteString Word8
  ListLike [a] a
  (Integral i, Ix i) = ListLike (Array i e) e
  (Ord key, Eq val) = ListLike (Map key val) (key, val)

These instances use the native underlying calls where appropriate (for
instance, ByteString and Data.List both provide a 'head').  The
typeclass also contains large numbers of default implementations, such
that only four functions must be implemented to make a type a member
of ListLike.  API ref is at 

  
http://software.complete.org/listlike/static/doc/ListLike/Data-ListLike.html#intro

Now, the questions:

1) Does everyone agree with me that we have a problem here?

2) Would it make sense to make ListLike, or something like it,
   part of the Haskell core?

3) Would it make sense to base as much code as possible in the Haskell
   core areound ListLike definitions?  Here I think of functions such
   as lines and words, which make sense both on [Char] as well as
   ByteStrings.

4) We are missing one final useful type: a Word32-based ByteString.
   When working in the Unicode character set, a 32-bit character
   can indeed be useful, and I could see situations in which the
   performance benefit of a ByteString-like implementation could
   be useful combared to [Char].

[1] Yes, I have read about Parsec 3 being imminent, which is also great

[2] http://software.complete.org/listlike



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


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Ross Paterson
On Wed, Feb 20, 2008 at 08:39:13AM -0600, John Goerzen wrote:
 I am concerned that the same thing is happening in Haskell.  We now
 have three common list-like types: the regular list, strict
 ByteString, and lazy ByteString.
 
 This has created some annoying situations.  For instance, a ByteString
 is great for reading data fast, but Parsec doesn't work on
 ByteStrings.  I am glad that someone wrote a Parsec equivalent that
 does[1], which answers a real need.  But this means that all the
 combinators in the hsemail library that implement standard RFC
 conventions won't be usable in my ByteString code, for instance.
 [...]
   http://software.complete.org/listlike/static/doc/ListLike/Data-ListLike.html

As Henning pointed out, multiple parameter type classes are problematic
for core libraries at present.

An alternative might be explicit dictionaries.  For example, a partial
solution would be to provide coinductive views, i.e. for all these types
to provide functions of a type like

full - Maybe (item, full)

(Data.Map, Data.Set and Data.Sequence would each have two such functions),
and to have a library of generalized functions taking such functions as
parameters, like

splitAt :: (full - Maybe (item, full)) -
Int - full - ([item], full)

Parsing libraries could include a similar parameter within their monad.

That only covers the elimination side, of course.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Selecting Array type

2008-02-20 Thread Brent Yorgey
2008/2/19 Jeff φ [EMAIL PROTECTED]:


 instance SmartArraySelector UArray Bool   where
 instance SmartArraySelector UArray Char   where
 instance SmartArraySelector UArray Double where
 instance SmartArraySelector UArray Float  where
 instance SmartArraySelector UArray Intwhere


Well, I'm not sure of the answer to your question, so I'll just make a
frivolous observation instead: I think you can leave off the where on
instances without any method definitions.

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


[Haskell-cafe] First Call for Papers -- GPCE'08

2008-02-20 Thread Emir Pasalic


  Call for Papers

 Seventh International Conference on
Generative Programming and Component Engineering (GPCE 2008)

 October 19-23, 2008
 Nashville, Tennessee
(co-located with OOPSLA 2008)

  http://www.gpce.org


Important Dates:

* Submission of abstracts:May 12, 2008
* Submission: May 19, 2008
* Notification:   June 30, 2008

* Tutorial and workshop proposals:March 30, 2008
* Tutorial and workshop notification: April 5, 2008

Scope

Generative and component approaches are revolutionizing software
development similar to how automation and components revolutionized
manufacturing. Generative Programming (developing programs that
synthesize other programs), Component Engineering (raising the level
of modularization and analysis in application design), and
Domain-Specific Languages (DSLs) (elevating program specifications to
compact domain-specific notations that are easier to write, maintain,
and analyze) are key technologies for automating program development.

The International Conference on Generative Programming and Component
Engineering provides a venue for researchers and practitioners
interested in techniques for enhancing the productivity, quality, and
time-to-market in software development that stems from deploying
components and automating program generation. In addition to exploring
cutting-edge techniques for developing generative and component-based
software, our goal is to foster further cross-fertilization between
the software engineering research community and the programming
languages community.

Submissions

Research papers:

10 pages in SIGPLAN proceedings style (sigplanconf.cls) reporting
original research results that contribute to scientific knowledge in
the areas listed below (the PC chair can advise on appropriateness).

Experience reports:

2 to 4 pages in length in SIGPLAN proceedings style
(sigplanconf.cls). We encourage experience reports that provide
concrete evidence with regards to the efficacy of generative
technologies in industrial applications.

Topics

GPCE seeks contributions in software engineering and in programming
languages related (but not limited) to:

* Generative programming
  o Reuse, meta-programming, partial evaluation, multi-stage  
and

multi-level languages, step-wise refinement,
and generic programming
  o Semantics, type systems, symbolic computation, linking and
explicit substitution, in-lining and macros, templates, and
program transformation
  o Runtime code generation, compilation, active libraries,
synthesis from specifications, development methods,  
generation of

non-code artifacts, formal methods, and reflection
* Generative techniques for
  o Product-line architectures
  o Distributed, real-time and embedded systems
  o Model-driven development and architecture
  o Resource bounded/safety critical systems.
* Component-based software engineering
  o Reuse, distributed platforms and middleware, distributed
systems, evolution, patterns, development methods,  
deployment and

configuration techniques, and formal methods
* Integration of generative and component-based approaches
* Domain engineering and domain analysis
  o Domain-specific languages including visual and UML-based  
DSLs

* Separation of concerns
  o Aspect-oriented and feature-oriented programming,
  o Intentional programming and multi-dimensional separation of
concerns
* Industrial applications of the above

Experience reports on applications of these techniques to real-world
problems are especially encouraged, as are research papers that relate
ideas and concepts from several of these topics, or bridge the gap
between theory and practice. The program chair is happy to advise on
the appropriateness of a particular subject.

Submissions must adhere to SIGPLAN's republication policy. Please  
contact
the program chair if you have any questions about how this policy  
applies

to your paper (gpce2008 at gpce.org).

Organizers

  General Chair: Yannis Smaragdakis (University of Oregon)
  Program Chair: Jeremy Siek (University of Colorado at Boulder)
  Satellite Chair: Ralf Lammel (Univ. Koblenz-Landau)
  Publicity Chair: Emir Pasalic (LogicBlox, Inc.)

Program Committee

  David Abrahams (Boost Consulting)
  Uwe Assmann (Technische Universitat, Dresden)
  Ira Baxter (Semantic Designs, USA)
  Martin Bravenboer (Delft Univ. of Tech., The Netherlands)
  Jacques Carette (McMaster University, Canada)
  Shigeru Chiba (Tokyo Institute of Technology, Japan)
  William R. Cook (University of Texas at 

Re: [Haskell-cafe] Selecting Array type

2008-02-20 Thread Henning Thielemann

On Wed, 20 Feb 2008, Brent Yorgey wrote:


2008/2/19 Jeff ö [EMAIL PROTECTED]:



 instance SmartArraySelector UArray Bool   where
 instance SmartArraySelector UArray Char   where
 instance SmartArraySelector UArray Double where
 instance SmartArraySelector UArray Float  where
 instance SmartArraySelector UArray Intwhere


Well, I'm not sure of the answer to your question, so I'll just make a 
frivolous observation instead: I think you can leave off the where on 
instances without any method definitions.


Haddock 0.* makes a difference at this point.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, Ross Paterson [EMAIL PROTECTED] wrote:
 conventions won't be usable in my ByteString code, for instance.
 [...]
   
 http://software.complete.org/listlike/static/doc/ListLike/Data-ListLike.html

 As Henning pointed out, multiple parameter type classes are problematic
 for core libraries at present.

 An alternative might be explicit dictionaries.  For example, a partial
 solution would be to provide coinductive views, i.e. for all these types
 to provide functions of a type like

   full - Maybe (item, full)

Hrm, what exactly is the return data here?  Is is the head and the
tail if the list has = 1 item, or Nothing otherwise?  Or...?

The problem with this approach, if my guess is correct, is that you
can't achieve native speed because you will have to be re-implementing
everything in terms of these functions.  For instance, I'd be using a
re-implementation of length instead of a native ByteString length,
which may be much faster.

I notice that Data.Foldable does some similar things but does not use
multi-parameter type classes.  I seem to recall that I attempted to do
this in the same manner, but got tripped up somewhere.  I can't
remember now exactly what the problem was, but I can go back and look
if nobody knows off-hand.

What is the problem with MPTC in base?


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


[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, John Goerzen [EMAIL PROTECTED] wrote:
 I notice that Data.Foldable does some similar things but does not use
 multi-parameter type classes.  I seem to recall that I attempted to do
 this in the same manner, but got tripped up somewhere.  I can't
 remember now exactly what the problem was, but I can go back and look
 if nobody knows off-hand.

I went back and looked.

The problem is that ByteString doesn't work as a member of Foldable,
or of ListLike without it being MPTC.  Trying to do so yields:

ListLike.hs:217:20:
Kind mis-match
Expected kind `* - *', but `BS.ByteString' has kind `*'
In the instance declaration for `F.Foldable BS.ByteString'

Is there any way around that, other than MPTC?

-- John


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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Neil Mitchell
Hi

 full - Maybe (item, full)

  Hrm, what exactly is the return data here?  Is is the head and the
  tail if the list has = 1 item, or Nothing otherwise?  Or...?

Yes, its the projection onto another type:

[] = Nothing
(x:xs) = Just (x, xs)

  What is the problem with MPTC in base?

MPTC is not a part of any Haskell standard. The rules surrounding MPTC
are not clear. People want to remove MPTC's/functional dependencies,
or modify them with associated types. Compilers such as nhc and yhc
can't implement them. Once they are in Haskell', with an associated
set of restrictions/overlap rules etc, then they can be freely used
with the base library.

Thanks

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


[Haskell-cafe] Problem with Python AST

2008-02-20 Thread Roel van Dijk
Hello everyone,

I am trying to create an AST for Python. My approach is to create a
data type for each syntactic construct. But I am stuck trying to
statically enforce some constraints over my statements. A very short
example to illustrate my problem:


newtype Ident = Id String

data BinOp = Add
   | Sub

data Exp = IntLit Integer
 | BinOpExp BinOp Exp Exp

data NormalCtx
data LoopCtx

data Statement ctx where
  Compound :: Compound - Statement ctx
  Pass :: Statement ctx
  Break:: Statement LoopCtx

newtype Global = Global [Ident]

data Suite ctx = Suite [Global] [Statement ctx]

type Else = Suite NormalCtx

data Compound = If [(Exp, Suite NormalCtx)] (Maybe Else)
  | While Exp (Suite LoopCtx) (Maybe Else)

newtype Program = Program [Statement NormalCtx]


The global statement makes an identifier visible in the local scope.
It holds for the entire current code block. So it also works
backwards, which is why I didn't make it a statement but part of a
suite (= block of statements).

Some statements may occur in any context, such as the pass
statement. But others are only allowed in certain situations, such as
the break statement. This is why I defined the Statement as a GADT.
I just supply the context in which the statement may be used and the
typechecker magically does the rest.

Feeling very content with this solution I tried a slightly more
complex program and discovered that my AST can not represent this
Python program:

for i in range(10):
  if i == 6:
break

The compound if statement is perfectly valid nested in the loop
because the Compound constructor of Statement allows any context. But
the suites inside the clauses of the if statement only allow normal
contexts. Since Break has a LoopCtx the typechecker complains.

Is there some other way to statically enforce that break statements
can only occur _nested_ inside a loop? There is a similar problem with
return statements that may only occur in functions. These nested
statements should somehow 'inherit' a context, if that makes any sense
:-)

I know I can simply create separate data types statements that can
occur inside loops and function bodies. But that would make the AST a
lot more complex, something I try to avoid. Python's syntax is already
complex enough!

Most of these constraints are not in the EBNF grammar which can be
found in the language reference, but they are specified in the
accompanying text. The cpython interpreter will generate SyntaxError's
when you violate these constraints.

See also Python's language reference:
http://docs.python.org/ref/ref.html (see sections 6 and 7)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-20 Thread Alfonso Acosta
On Wed, Feb 20, 2008 at 11:26 AM, Wolfgang Jeltsch
[EMAIL PROTECTED] wrote:
  Hello Fons,

  why do you use the term vector?  I'd say that this term is more or less wrong
  for what this type is about.  The distinguishing property of vectors compared
  to lists is that there is addition and scalar multiplication for vectors.

That depends on how you interpret the word vector, which is
polysemous: http://en.wikipedia.org/wiki/Vector

You are interpreting it as An element in a vector space, often
represented as a coordinate vector whereas in this case I try to mean
A one-dimensional array.

 The data type you defined is a fixed size list.

The fact that FSVec is internally implemented using lists doesn't
imply that FSVec should be interpreted as a list. FSVec is an ADT and
I could as well have used something else to implement it (inmutable
arrays for instance).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with Python AST

2008-02-20 Thread Daniel Gorín

Hi

Something like this would do?

if_ = Compound $ If [(IntLit 6, Suite [] [Break])] Nothing
while_ = Compound $ While (IntLit 6) (Suite [] [if_]) Nothing

f = Program [while_]

-- this one fails
-- f2 = Program [if_]


newtype Ident = Id String

data BinOp = Add
   | Sub

data Exp = IntLit Integer
 | BinOpExp BinOp Exp Exp

data NormalCtx
data LoopCtx

data Statement ctx where
  Compound :: Compound ctx - Statement ctx
  Pass :: Statement ctx
  Break:: Statement LoopCtx

newtype Global = Global [Ident]

data Suite ctx = Suite [Global] [Statement ctx]

type Else ctx = Suite ctx

data Compound ctx where
If:: [(Exp, Suite ctx)] - Maybe (Else ctx) - Compound ctx
While :: Exp - (Suite LoopCtx) -  Maybe (Else LoopCtx) -  
Compound ctx


newtype Program = Program [Statement NormalCtx]

Daniel

On Feb 20, 2008, at 5:12 PM, Roel van Dijk wrote:


Hello everyone,

I am trying to create an AST for Python. My approach is to create a
data type for each syntactic construct. But I am stuck trying to
statically enforce some constraints over my statements. A very short
example to illustrate my problem:


newtype Ident = Id String

data BinOp = Add
   | Sub

data Exp = IntLit Integer
 | BinOpExp BinOp Exp Exp

data NormalCtx
data LoopCtx

data Statement ctx where
  Compound :: Compound - Statement ctx
  Pass :: Statement ctx
  Break:: Statement LoopCtx

newtype Global = Global [Ident]

data Suite ctx = Suite [Global] [Statement ctx]

type Else = Suite NormalCtx

data Compound = If [(Exp, Suite NormalCtx)] (Maybe Else)
  | While Exp (Suite LoopCtx) (Maybe Else)

newtype Program = Program [Statement NormalCtx]


The global statement makes an identifier visible in the local scope.
It holds for the entire current code block. So it also works
backwards, which is why I didn't make it a statement but part of a
suite (= block of statements).

Some statements may occur in any context, such as the pass
statement. But others are only allowed in certain situations, such as
the break statement. This is why I defined the Statement as a GADT.
I just supply the context in which the statement may be used and the
typechecker magically does the rest.

Feeling very content with this solution I tried a slightly more
complex program and discovered that my AST can not represent this
Python program:

for i in range(10):
  if i == 6:
break

The compound if statement is perfectly valid nested in the loop
because the Compound constructor of Statement allows any context. But
the suites inside the clauses of the if statement only allow normal
contexts. Since Break has a LoopCtx the typechecker complains.

Is there some other way to statically enforce that break statements
can only occur _nested_ inside a loop? There is a similar problem with
return statements that may only occur in functions. These nested
statements should somehow 'inherit' a context, if that makes any sense
:-)

I know I can simply create separate data types statements that can
occur inside loops and function bodies. But that would make the AST a
lot more complex, something I try to avoid. Python's syntax is already
complex enough!

Most of these constraints are not in the EBNF grammar which can be
found in the language reference, but they are specified in the
accompanying text. The cpython interpreter will generate SyntaxError's
when you violate these constraints.

See also Python's language reference:
http://docs.python.org/ref/ref.html (see sections 6 and 7)
___
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] Re: The Proliferation of List-Like Types

2008-02-20 Thread Jules Bean

John Goerzen wrote:

On 2008-02-20, John Goerzen [EMAIL PROTECTED] wrote:

I notice that Data.Foldable does some similar things but does not use
multi-parameter type classes.  I seem to recall that I attempted to do
this in the same manner, but got tripped up somewhere.  I can't
remember now exactly what the problem was, but I can go back and look
if nobody knows off-hand.


I went back and looked.

The problem is that ByteString doesn't work as a member of Foldable,
or of ListLike without it being MPTC.  Trying to do so yields:

ListLike.hs:217:20:
Kind mis-match
Expected kind `* - *', but `BS.ByteString' has kind `*'
In the instance declaration for `F.Foldable BS.ByteString'

Is there any way around that, other than MPTC?


Not directly, no.

The point about Foldable, Functor, and Monad, is that they enforce the 
connection between container and contents. If the contents is of type 
a, the container is of type f a for a fixed type constructor 'f'. 
This works for [], Seq, and so on, but fails for ByteString.


To go to the next level, for ByteString you either need type-level 
functions (to generalise 'f' from type constructor to arbitrary 
function :: * - *), or MPTCs (to make the association between 
container and contents explicit).


However, passing around dictionaries is certainly a solution which works 
in haskell98. I haven't thought it through enough to see if it would be 
unpleasantly verbose in practice.


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


Re: [Haskell-cafe] stream/bytestring questions

2008-02-20 Thread Chad Scherrer
On Feb 17, 2008 6:06 PM, Derek Elkins [EMAIL PROTECTED] wrote:
 It's -quite- possible that a coalgebraic perspective is much more
 natural for your code/problem.  If that's the case, use it (the
 coalgebraic perspective that is).  Obviously depending on the internals
 of the stream library is not a good idea and using Streams directly was
 not their intent, but it is your code.  Do what you will.

Here's an example of the problem. Start with a function

extract :: [Int] - [a] - [a]
extract = f 0
where
f !k nss@(n:ns) (x:xs)
  | n == k= x : f (k+1) ns xs
  | otherwise = f (k+1) nss xs
f _ _ _ = []

which is just a more efficient way of getting
extract ns xs == [xs !! n | n - ns]

There should be a way to write this that will be friendly for stream
fusion. The best option I can see is unfoldr. But if you try to write
it this way, you get something like

extract' ns xs = unfoldr f (0,ns,xs)
  where
  f (!k, nss@(n:ns), x:xs)
| n == k= Just (x, (k + 1, ns, xs))
| otherwise = f (k+1, nss, xs)
  f _ = Nothing

This is fine, except that the second-to-last line means this is still
recursive. If I understand correctly, fusion requires that the
recursion be encapsulated within the unfoldr or other functions that
are expressed internally as stream functions.

We could encapsulate the recursion with a function
stepUnfoldr :: (s - Step a s) - s - [a]
stepUnfoldr f s = unfoldr g s
  where
  g s = case f s of
Done - Nothing
Yield x s' - Just (x,s')
Skip s' - g s'

Using this, we could just write

extract'' ns xs = stepUnfoldr f (0,ns,xs)
  where
  f (!k, nss@(n:ns), x:xs)
| n == k= Yield x (k + 1, ns, xs)
| otherwise = Skip (k+1, nss, xs)
  f _ = Done

This is a pretty natural way to write the algorithm, and the recursion
is nicely tucked away. The only remaining question is whether we can
get things to fuse.

The type of stepUnfoldr looks familiar...

*Main :t stepUnfoldr
stepUnfoldr :: (s - Step a s) - s - [a]

*Main :t \f s - unstream $ Stream f s
\f s - unstream $ Stream f s :: (Data.Stream.Unlifted s) =
 (s - Step a s) - s - [a]

If we could somehow swap out our state type for an unlifted one, we
could write a rule
  stepUnfoldr f = unstream . Stream f

It seems like there might be some subtleties there to watch out for,
but I'm not sure yet.

Anyway, this is the kind of thing I had in mind when I asked about
using the internals of Data.Stream more directly.

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


[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
Henning Thielemann lemming at henning-thielemann.de writes:
  4) We are missing one final useful type: a Word32-based ByteString.
When working in the Unicode character set, a 32-bit character
can indeed be useful, and I could see situations in which the
performance benefit of a ByteString-like implementation could
be useful combared to [Char].
 
 StorableVector should fill this gap.
http://code.haskell.org/~sjanssen/storablevector/
 

Yes, it could, but 
(1) it's way behind ByteString in terms of optimizations (== fusion)
(2) there's (as far as I know) not a StorableVector.Lazy, which is very much
needed

To catch up on both fronts, we're looking at a lot of duplicate code.

Chad

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Antoine Latter
On Feb 20, 2008 12:48 PM, Chad Scherrer [EMAIL PROTECTED] wrote:
  StorableVector should fill this gap.
 http://code.haskell.org/~sjanssen/storablevector/
 

 Yes, it could, but
 (1) it's way behind ByteString in terms of optimizations (== fusion)
 (2) there's (as far as I know) not a StorableVector.Lazy, which is very much
 needed

 To catch up on both fronts, we're looking at a lot of duplicate code.

For anyone looking into it - the StorableVector fusion would have to
be quite different from the current ByteString fusion framework.
Maybe it would be enough to lay down a Stream fusion framework for
StorableVectors.

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote:
 For anyone looking into it - the StorableVector fusion would have to
 be quite different from the current ByteString fusion framework.
 Maybe it would be enough to lay down a Stream fusion framework for
 StorableVectors.

I must be missing something. Why would it have to be so different?

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


[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote:
 Not directly, no.

 The point about Foldable, Functor, and Monad, is that they enforce the 
 connection between container and contents. If the contents is of type 
 a, the container is of type f a for a fixed type constructor 'f'. 
 This works for [], Seq, and so on, but fails for ByteString.

Right.  In a pure abstract sense, we humans know there is a
relationship between container and contents: a ByteString always
contains a Word8 (or a Char8 if we choose the alternative
implementation).

But that is not expressed in the type of ByteString.

 However, passing around dictionaries is certainly a solution which works 
 in haskell98. I haven't thought it through enough to see if it would be 
 unpleasantly verbose in practice.

I'm not sure precisely what you mean here.  If you mean to use
dictionaries instead of typeclasses entirely, yes of course that would
work, but it would mean that the functions could not operate on the
underlying types unmodified, and once again compatibility issues may
arise.

On the other hand, if you mean using a dictionary to wrap just the
ByteString types (or other similar ones), I am currently thinking of
something along those lines.  I'll post here if I come up with
something clever (or not).



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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Antoine Latter
On Feb 20, 2008 12:59 PM, Chad Scherrer [EMAIL PROTECTED] wrote:
 On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote:
  For anyone looking into it - the StorableVector fusion would have to
  be quite different from the current ByteString fusion framework.
  Maybe it would be enough to lay down a Stream fusion framework for
  StorableVectors.

 I must be missing something. Why would it have to be so different?


From what I saw of Data.ByteString.Fusion, it relies on the assumption
that the elements of the output array are of the same size and
alignment as the elements of all of the arrays in the fused
intermediate steps.  That way, all of the intermediate stages can
mutate the output array in place.

This works because all of the fusable bytestring functions have types
along the lines of:

map :: (Word8 - Word8) - ByteString - ByteString

With StorableVector, it'd be nice to support the fusion of:

map :: (a - b) - Vector a - Vector b

All of this just comes from me reading the code, so I could be
miss-interpreting something.

The NDP papers probably have something interesting to say about this,
but I haven't taken the time to try and understand/simplify what they
do.

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


Re: [Haskell-cafe] Doubting Haskell

2008-02-20 Thread Alan Carter
Cale,

On Feb 20, 2008 10:58 AM, Cale Gibbard [EMAIL PROTECTED] wrote:
 (I'm copying the list on this, since my reply contains a tutorial
 which might be of use to other beginners.)

Thank you so much for this - I've just started playing with it so few
intelligent responses yet. I'm sure it will be of *huge* use to
others, right in the middle of the gap I fell into.

The experiment continues - I'll be back :-)

Many thanks,

Alan

-- 
... the PA system was moaning unctuously, like a lady hippopotamus
reading A. E. Housman ...
  -- James Blish, They Shall Have Stars
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Broken http://darcs.haskell.org/darcsweb/?

2008-02-20 Thread Dominic Steinitz
I'm getting errors when I click on any of the links. I'm not sure who
administers the site.

IOError Python 2.4.4: /usr/bin/python
Wed Feb 20 11:41:13 2008

A problem occurred in a Python script. Here is the sequence of function
calls leading up to the error, in the order they occurred.
 /srv/darcsweb/darcsweb.cgi
 2248 url_request.sort()
 2249 cache = Cache(config.cachedir, url_request)
 2250 if cache.open():
 2251 # we have a hit, dump and run
 2252 cache.dump()
cache = __main__.Cache instance, cache.open = bound method Cache.open
of __main__.Cache instance
 /srv/darcsweb/darcsweb.cgi in open(self=__main__.Cache instance)
  466 pid = str(os.getpid())
  467 fname = self.basedir + '/.' + self.fname +
'-' + pid
  468 self.file = open(fname, 'w')
  469 self.mode = 'w'
  470
self = __main__.Cache instance, self.file = None, builtin open = type
'file', fname =
'/tmp/darcsweb-cache/.3647210cedbbeff551e4ffe8dac1328a00518335-30974'

IOError: [Errno 2] No such file or directory:
'/tmp/darcsweb-cache/.3647210cedbbeff551e4ffe8dac1328a00518335-30974'
  args = (2, 'No such file or directory')
  errno = 2
  filename =
'/tmp/darcsweb-cache/.3647210cedbbeff551e4ffe8dac1328a00518335-30974'
  strerror = 'No such file or directory'

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
Antoine Latter [EMAIL PROTECTED] wrote:
 From what I saw of Data.ByteString.Fusion, it relies on the assumption
 that the elements of the output array are of the same size and
 alignment as the elements of all of the arrays in the fused
 intermediate steps.  That way, all of the intermediate stages can
 mutate the output array in place.

I see a lot in there involving the elimination of intermediate data
structures, but nothing about destructive updates. The API is purely
functional, and what you're talking about would need to be done in the
IO monad to be sure you don't throw away stuff you might need to use
again.

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


[Haskell-cafe] Re: Arrows: definition of pure arr

2008-02-20 Thread Ben Franksen
Wolfgang Jeltsch wrote:
 I’m also in the process of shortening the names for type variables since
 in conference papers you cannot use names that long (because otherwise you
 quickly overrun the available width) and I don’t want to have too many
 differences between papers and actual source code.  However, I still don’t
 like single-letter names like a and b.

I like them if the type variables are really completely arbitrary types,
like in map :: (a-b) - [a] - [b]. Using longer and more descriptive
names here would (IMHO) be a mistake, as there is nothing specific about
them. Similar on the value level, a definition like map f (x:xs) = f x :
map f xs is (IMO) rather /easier/ to understand than anything using longer
and more descriptive names, as, again, what x stands for is completely
irrelevant here.

I'd like to mention in passing that according to Dijkstra, when we develop
an abstraction, it is important to (at least temporarily) forget what the
symbols originally stood for, that is, before we abstracted them out of the
context in which they originally appeared. The advantage is that
without 'intuition' (about what the symbols 'mean') we have nothing left to
follow but logic, which (supposedly) leads to a clearer understanding of
the abstraction in itself, which in turn leads to shorter and more concise
proofs, i.e. programs.

That said, there are many situations where the type variables are linked by
constraints and additional type (e.g. class method) signatures. In this
case, mnemonic names can be a great help to understanding. In the example
given, I'd use one-letter abbreviations of teh longer names, i.e.

  create :: PlainCircuit i o - i - IO (o, IO ())

Cheers
Ben

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


[Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
-- proposition
data Prp a = Var a
   | Not (Prp a)
   | Or  (Prp a) (Prp a)
   | And (Prp a) (Prp a)
   | Imp (Prp a) (Prp a)
   | Xor (Prp a) (Prp a)
   | Eqv (Prp a) (Prp a)
   | Cns Bool
   deriving (Show, Eq)

-- Here are to variable extraction methods

-- variable extraction reference imp.
-- Graham Hutton: Programming in Haskell, 107
vars_ :: Prp a → [a]
vars_ (Cns _)   = []
vars_ (Var x)   = [x]
vars_ (Not p)   = vars_ p
vars_ (Or  p q) = vars_ p ++ vars_ q
vars_ (And p q) = vars_ p ++ vars_ q
vars_ (Imp p q) = vars_ p ++ vars_ q
vars_ (Xor p q) = vars_ p ++ vars_ q
vars_ (Eqv p q) = vars_ p ++ vars_ q

-- variable extraction new * this is faster
vars :: Prp a → [a]
vars p = evs [p]
  where
evs []   = []
evs (Cns _  :ps) = []
evs (Var x  :ps) = x:evs ps
evs (Not p  :ps) = evs (p:ps)
evs (Or  p q:ps) = evs (p:q:ps)
evs (And p q:ps) = evs (p:q:ps)
evs (Imp p q:ps) = evs (p:q:ps)
evs (Xor p q:ps) = evs (p:q:ps)
evs (Eqv p q:ps) = evs (p:q:ps)

-- for  : Not (Imp (Or (Var 'p') (Var 'q')) (Var p))
-- vars_: ['p','q','p']
-- vars : ['p','q','p']

-- order and the fact that 'p' appears twice being irrelevant:
-- is there an even faster way to do this?
--
-- Cetin Sert
-- www.corsis.de
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: a help for install

2008-02-20 Thread Ben Franksen
Wolfgang Jeltsch wrote:
 Am Montag, 18. Februar 2008 19:46 schrieb Carlos Gomez A.:
 hi, my name is carlos

 I need information for correct installor

 what are dependencies on ghc ?

 I have a Debian System.
 
 Always use your distribution’s packages until they aren’t any or there is
 good
 reason not to do so.  Try “aptitude install ghc6”.

For my system (kubuntu 7.10) ghc-6.8.2 is not available as a package, only
6.6.1. And there are programs and libraries that can't be used with 6.6.1.

Furthermore, in kubuntu 7.10 the libghc6 packages are broken w.r.t the
documentation path. To illustrate (I have both libghc6-mtl-dev and
libghc6-mtl-doc installed):

[EMAIL PROTECTED]: ~  ghc-pkg describe mtl | grep haddock
haddock-interfaces: /usr/share/mtl-1.0.1/doc/html/mtl.haddock
haddock-html: /usr/share/mtl-1.0.1/doc/html
[EMAIL PROTECTED]: ~  ls /usr/share/mtl-1.0.1/doc/html
ls: /usr/share/mtl-1.0.1/doc/html: No such file or directory

[EMAIL PROTECTED]: ~  locate mtl.haddock
/usr/share/doc/ghc6-doc/html/libraries/mtl/mtl.haddock
[EMAIL PROTECTED]: ~  ls /usr/share/doc/ghc6-doc/html/libraries/mtl/mtl.haddock
/usr/share/doc/ghc6-doc/html/libraries/mtl/mtl.haddock

This leads to errors when haddock tries to link to the mtl documentation. It
took me quite a while to figure out what the source of this problem was.

IME, it is better to install ghc and all the libraries from source. Of
course you need to install ghc from the distro package for bootstrapping
ghc, but you can delete it after the self-compiled ghc is installed.

Cheers
Ben

PS: Yes, I reported this bug to the package maintainer but I received no
response.

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


Re: [Haskell-cafe] Exporting Haskell Libraries to C Programmers

2008-02-20 Thread Don Stewart
joseph.bruce:
 Hi,
 
 I have a Haskell library that I want to make available via FFI to C
 programmers on my project team.  I read this thread
 (http://thread.gmane.org/gmane.comp.lang.haskell.cafe/21447) which had
 some interesting ideas, but they seemed unresolved.  Or maybe it answers
 my question but I don't understand it.
 
 Is there a way I can package (ghc-)compiled Haskell code into a
 statically-linked library and not force the C programmers to include
 headers and libraries that they have no knowledge of and undefine a
 seemingly endless list of preprocessor symbols (run ghc with the verbose
 flag and look at the calls to gcc)?  Can this process be automated?

Yes, check the FFI documentation for the main story. 

In short, build the Haskell code with cabal, with your foreign export
Haskell functions in the cbits. That bundle can then be linked against
C code.

You do need to link your app against libHSrts.a and libHSbase.a (and
other libs you use), but assuming you foreign export, the code 
to call will look just like normal C stuff.

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


[Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Steve Lihn
I proudly announce a little toy that lists the frequency of modules
being imported by other modules. Do you know Control.Monad is the most
frequently imported module? I did not!

Currently it only includes GHC 6.8 core library. If you have any idea
how to parse through HackageDB code, please let me know.

http://haskell.ecoin.net/cgi-bin/modules.pl

Disclaimer: This is entirely for fun. It is by no means accurate or
complete. I only spent a couple hours on a little perl script and a
mysql table...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Broken http://darcs.haskell.org/darcsweb/?

2008-02-20 Thread Ian Lynagh
On Wed, Feb 20, 2008 at 07:28:54PM +, Dominic Steinitz wrote:
 I'm getting errors when I click on any of the links.

I've created /tmp/darcsweb-cache and made it writable, which seems to
have made it work again.

 I'm not sure who administers the site.

Neither am I, but it needs some tweaking or it will break whenever monk
is rebooted. It would be useful if an admin address could be put on the
pages, too.


Thanks
Ian

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


[Haskell-cafe] Re: Selecting Array type

2008-02-20 Thread Ben Franksen
Jeff φ wrote:
 However, my implementation of SmartArray requires me to create an instance
 of a selector class to tell the compiler whether the type is boxed or
 unboxed.  I'm hoping to avoid creating instances of the selector class for
 every possible type.  I'd be grateful for any suggestions.

Using ghc-6.8.2 I get

test.hs:30:0:
Functional dependencies conflict between instance declarations:
  instance [overlap ok] SmartArraySelector UArray Bool
-- Defined at test.hs:30:0-46
  instance [overlap ok] SmartArraySelector Array e
-- Defined at test.hs:49:0-40

[more of the same for the other classes omitted]

The offending lines are

instance SmartArraySelector UArray Bool   where

vs.

instance SmartArraySelector Array e where

Note that it explicitly says 'overlap ok' but the functional dependencies
cannot be fulfilled. You defined

class (IArray a e) = SmartArraySelector a e | e - a

Your generic instance says that it determines the 'a' type for /all/
types 'e' as 'Array'. This conflicts with the other instance which says it
determines the 'a' for the specific type 'Bool' as 'UArray'.

That leaves the question how to achieve what you want, for which
unfortunately I have no answer.

Cheers
Ben

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


[Haskell-cafe] Fwd: NW Functional Programming Interest Group

2008-02-20 Thread Greg Meredith
All,

Apologies for multiple listings.

This is just a friendly reminder that a small cadre of us are organizing a
Northwest Functional Programming Interest Group. Our first official meeting
is today at the

The Seattle Public Library
1000 - 4th Ave.
Seattle, WA  98104

Spiral 6 Conference Room from 17:00 - 18:00 on February 20th.

On the first meeting's agenda we'll be

   - giving people who are interested in or actively using FP for work or
   play a chance to meet
   - seeking to build up a pipeline of presentations and guest speakers
   - trying to keep organizational mishigosh to a minimum

Hope to see you there.

Monadically yours,

--greg

-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
806 55th St NE
Seattle, WA 98105

+1 206.650.3740

http://biosimilarity.blogspot.com



-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
806 55th St NE
Seattle, WA 98105

+1 206.650.3740

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


[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Ben Franksen
John Goerzen wrote:

 On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote:
 Not directly, no.

 The point about Foldable, Functor, and Monad, is that they enforce the
 connection between container and contents. If the contents is of type
 a, the container is of type f a for a fixed type constructor 'f'.
 This works for [], Seq, and so on, but fails for ByteString.
 
 Right.  In a pure abstract sense, we humans know there is a
 relationship between container and contents: a ByteString always
 contains a Word8 (or a Char8 if we choose the alternative
 implementation).
 
 But that is not expressed in the type of ByteString.

Hm, making a function out of a constant is easy on the value level, just use
(const x) instead of (x). So, what about wrapping ByteString in a GADT,
like this

  data ByteString' a where
BS' :: Word8 - ByteString' Word8

? I probably overlooked something important here...

Cheers
Ben

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread David Roundy
On Wed, Feb 20, 2008 at 11:18:51PM +0100, Ben Franksen wrote:
 John Goerzen wrote:
 
  On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote:
  Not directly, no.
 
  The point about Foldable, Functor, and Monad, is that they enforce the
  connection between container and contents. If the contents is of type
  a, the container is of type f a for a fixed type constructor 'f'.
  This works for [], Seq, and so on, but fails for ByteString.
  
  Right.  In a pure abstract sense, we humans know there is a
  relationship between container and contents: a ByteString always
  contains a Word8 (or a Char8 if we choose the alternative
  implementation).
  
  But that is not expressed in the type of ByteString.
 
 Hm, making a function out of a constant is easy on the value level, just use
 (const x) instead of (x). So, what about wrapping ByteString in a GADT,
 like this
 
   data ByteString' a where
 BS' :: Word8 - ByteString' Word8
 
 ? I probably overlooked something important here...

The problem is that while this would change the kind of ByteString to the
same as the kind expected by Functor, you still couldn't define a proper
Functor instance, since only ByteString' Word8 can ever actually be
created.  i.e. how could you implement

fmapBS :: (a - b) - ByteString' a - ByteString' b
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: The Proliferation of List-Like Types

2008-02-20 Thread Ben Franksen
David Roundy wrote:
 On Wed, Feb 20, 2008 at 11:18:51PM +0100, Ben Franksen wrote:
 John Goerzen wrote:
  On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote:
  Not directly, no.
 
  The point about Foldable, Functor, and Monad, is that they enforce the
  connection between container and contents. If the contents is of type
  a, the container is of type f a for a fixed type constructor 'f'.
  This works for [], Seq, and so on, but fails for ByteString.
  
  Right.  In a pure abstract sense, we humans know there is a
  relationship between container and contents: a ByteString always
  contains a Word8 (or a Char8 if we choose the alternative
  implementation).
  
  But that is not expressed in the type of ByteString.
 
 Hm, making a function out of a constant is easy on the value level, just
 use (const x) instead of (x). So, what about wrapping ByteString in a
 GADT, like this
 
   data ByteString' a where
 BS' :: Word8 - ByteString' Word8
 
 ? I probably overlooked something important here...
 
 The problem is that while this would change the kind of ByteString to the
 same as the kind expected by Functor, you still couldn't define a proper
 Functor instance, since only ByteString' Word8 can ever actually be
 created.  i.e. how could you implement
 
 fmapBS :: (a - b) - ByteString' a - ByteString' b

Oh yes, indeed. I knew there would be a catch, somewhere...

Cheers
Ben

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


[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, John Goerzen [EMAIL PROTECTED] wrote:

 On the other hand, if you mean using a dictionary to wrap just the
 ByteString types (or other similar ones), I am currently thinking of
 something along those lines.  I'll post here if I come up with
 something clever (or not).

Can't come up with anything particularly clever here.  I think if we
go that route, our only option is to add some wrapping/dewrapping
function to encapsulate a ByteString into some sort of BSWrapper that
does this sort of thing.

Not exceptionally convenient.

-- John

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


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Duncan Coutts

On Wed, 2008-02-20 at 08:39 -0600, John Goerzen wrote:

 * The iconv library works only on lazy ByteStrings, and does not
handle Strings or strict ByteStrings

There is a very good reason for this. The right solution in this
particular example is not to overload every internal string operation in
the iconv lib (which would be far far too slow) but to convert to/from
your favourite representation on the edge. So in this case those
conversions would be pack/unpack or the similar equivalents for strict
- lazy bytestrings.

If we want it to be generic then we want a class of string like things
that provides conversions only, not operations.

For example we could export iconv as:

iconv :: StringLike string = Encoding - Encoding - string - string
iconv to from = (convertStringRep :: Lazy.ByteString - string)
  . theRealIconv
  . (convertStringRep :: string - Lazy.ByteString)

class StringLike string where
  ...

convertStringRep :: (StringLike s1, StringLike s2) = s1 - s2
-- analogous to fromIntegral


Duncan

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


Re: [Haskell-cafe] question about STM and IO

2008-02-20 Thread Bulat Ziganshin
Hello John,

Tuesday, February 12, 2008, 9:28:22 PM, you wrote:
 I was recently looking at the STM library, and I have a question about
 the function unsafeIOToSTM.  Can anyone explain to me what is unsafe
 about it, and what sort of use would be considered safe?

STM operations can be repeated if first transaction was unsuccessful.
so, you may se here only operations that may be safely repeated - say,
reading/writing memory areas, or reading/writing files, or even
sending network message as long as its duplication is ok

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Haddock documentation of Data.Array.* is confusing

2008-02-20 Thread Bulat Ziganshin
Hello Alfonso,

Tuesday, February 12, 2008, 11:32:20 PM, you wrote:

 Excuse me for the subject, but IMHO is absolutely true. Anyhow, the

of course, you are right, but for practical goals i may suggest just
to read module sources instead of reading [had]docs. seeing the
implementation is much more interesting, after all. especially when you
are so cool that you are going to add your own instance


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Wolfgang Jeltsch
Am Mittwoch, 20. Februar 2008 22:22 schrieb Steve Lihn:
 I proudly announce a little toy that lists the frequency of modules
 being imported by other modules. Do you know Control.Monad is the most
 frequently imported module? I did not!

This doesn’t surprise me very much.  What surprises me more is that OpenGL 
stuff is that popular. :-) 

 […]

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


Re: [Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Ross Paterson
On Wed, Feb 20, 2008 at 09:22:58PM +, Steve Lihn wrote:
 I proudly announce a little toy that lists the frequency of modules
 being imported by other modules. Do you know Control.Monad is the most
 frequently imported module? I did not!
 
 Currently it only includes GHC 6.8 core library. If you have any idea
 how to parse through HackageDB code, please let me know.

The layout is pretty simple.  The index file

http://hackage.haskell.org/packages/archive/00-index.tar.gz

contains all the .cabal files.  From their names you can figure out the
locations of the source bundles, e.g.

AGI/1.1/AGI.cabal
-
http://hackage.haskell.org/packages/archive/AGI/1.1/AGI-1.1.tar.gz

You can easily slurp the lot.

The HackageDB wiki page has more details:

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


Re: [Haskell-cafe] Where does ~ come from?

2008-02-20 Thread Steve Lihn
If ~ does not have any special meaning and it could be ### or xyz,
then how does GHC know to print
 a ~ b, but not ~ a b
 a ### b, but not ### a b
 xyz a b, but not a `xyz` b

Simply because xyz is alphanumeric?


On Wed, Feb 20, 2008 at 12:34 AM, David Menendez [EMAIL PROTECTED] wrote:
 On Feb 19, 2008 4:15 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
  Am Dienstag, 19. Februar 2008 18:26 schrieben Sie:
   […]
 
   However, I was told this:  ~ a b is a ~ b, but if I write c a b and
   wish the effect of a `c` b. This would not work. ~ as an infix operator
   has a special place in GHC. It is not just a type variable.
 
  Sorry, but I don't understand fully what you mean. :-(  But nevertheless,
  a ~ b is not the same as ~ a b but as (~) a b.  It's just like with
  ordinary operators where a + b is the same as (+) a b.

 Note that some (all?) versions of GHC will incorrectly print a ~ b
 as ~ a b.

 http://hackage.haskell.org/trac/ghc/ticket/1930

 Prelude :t undefined :: a + b
 undefined :: a + b :: forall (+ :: * - * - *) a b. + a b

 It mostly gets infix type constructors right, although there are
 apparently problems with precedence and associativity.

 --
 Dave Menendez [EMAIL PROTECTED]
 http://www.eyrie.org/~zednenem/

 ___
 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] Where does ~ come from?

2008-02-20 Thread Stefan O'Rear
On Wed, Feb 20, 2008 at 07:18:42PM -0500, Steve Lihn wrote:
 If ~ does not have any special meaning and it could be ### or xyz,
 then how does GHC know to print
  a ~ b, but not ~ a b
  a ### b, but not ### a b
  xyz a b, but not a `xyz` b
 
 Simply because xyz is alphanumeric?

Yes.

Stefan


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


Re: [Haskell-cafe] Haddock documentation of Data.Array.* is confusing

2008-02-20 Thread Alfonso Acosta
On Wed, Feb 20, 2008 at 10:17 PM, Bulat Ziganshin
[EMAIL PROTECTED] wrote:
 Hello Alfonso,


  Tuesday, February 12, 2008, 11:32:20 PM, you wrote:

   Excuse me for the subject, but IMHO is absolutely true. Anyhow, the

  of course, you are right, but for practical goals i may suggest just
  to read module sources instead of reading [had]docs.

Well, that's what I was forced to do in the end, but I still think
that the haddock documentation should be clear enough for most of the
cases, and, when it comes to  Data.Array* it could certainly be
improved.

 seeing the
  implementation is much more interesting, after all. especially when you
  are so cool that you are going to add your own instance

I don't think that being cool had anything to do with it. My only
purpose was to understand the desing of the interface for inmutable
arrays.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] haddock as a markdown preprocessor

2008-02-20 Thread Conal Elliott
There was a chat today on
#haskellhttp://tunes.org/%7Enef/logs/haskell/08.02.20
(15:08 to 16:10) about evolving haddock.  I'd like to get comments.

The goal is to get the full functionality of a general purpose,
programmer-friendly markup language like markdown.  One example is image
embedding.  Another is friendly links (no visible URL).

The idea is to make a future haddock be a *preprocessor* that generates
pandoc's extended markdown (or some such).  Documentation would be mostly
markdown, with very few extensions for code documentation ('foo' and 
Foo.Bar, maybe a bit more).  Most of the doc would simply be passed through
untouched.  The code-doc extensions would get rewritten into standard
markdown and mixed in with the rest.

Pandoc could then take the generated markdown and produce HTML, LaTeX,
DocBoook XML, etc.

Perhaps there will be ways in which markdown falls short in expressiveness.
If so, I'm guessing the shortcomings wouldn't be specific to the task of
code documentation, and so could be approached as improvements to
markdown/pandoc (which is written in Haskell).

Since the old and new doc languages would be quite incompatible, we might
want to specify in a .cabal file which language to use.

Reactions?

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


[Haskell-cafe] Re: Where does ~ come from?

2008-02-20 Thread Ben Franksen
Stefan O'Rear wrote:
 On Wed, Feb 20, 2008 at 07:18:42PM -0500, Steve Lihn wrote:
 If ~ does not have any special meaning and it could be ### or xyz,
 then how does GHC know to print
  a ~ b, but not ~ a b
  a ### b, but not ### a b
  xyz a b, but not a `xyz` b
 
 Simply because xyz is alphanumeric?
 
 Yes.

To slightly elaborate this: In Haskell, normal (prefix) functions and
operators (infix) functions are syntactically distinguished by the
characters they may contain: the former must contain only alphanumerics
plus ' and _, the latter only operator symbols such as !#$%*+./=[EMAIL 
PROTECTED]|-~
for details see the Haskell98 Report
(http://www.haskell.org/onlinelibrary/lexemes.html).

Cheers
Ben

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


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On Wednesday 20 February 2008 5:13:34 pm Duncan Coutts wrote:
 On Wed, 2008-02-20 at 08:39 -0600, John Goerzen wrote:
  * The iconv library works only on lazy ByteStrings, and does not
 handle Strings or strict ByteStrings

 There is a very good reason for this. The right solution in this
 particular example is not to overload every internal string operation in
 the iconv lib (which would be far far too slow) but to convert to/from

I guess the first question here is: in general, why?

Let's say you were using something like ListLike (or StringLike, see below).  
If a library used these operations exclusively, you could make it work on 
most any type of list by simply changing your imports.  (Hide the regular 
functions from Prelude, and import ListLike).  For types such as ByteStrings 
or lists, that already have a very rich native implementation of these 
functions, the native implementation is used.  You should be getting greater 
compatibility essentially for free.  ListLike is an exhaustive mapping over 
these native functions.  This would be great for anything from sort 
algorithms to parsers, etc.  I even have a ListLikeIO typeclass[2] to 
facilitate this. [2]

Now in your iconv case, you have a special case because you are doing 
manipulation specifically upon 8-bit binary data.  It may not make sense for 
you to support a [Char] or even a Char8 ByteString because it does not lend 
itself to those very well.  You could, perhaps, support a [Word8] as well as 
a ByteString when using ListLike.  That is, you may have a function like 
this:

head :: ListLike full Word8 = full - Word8

You could still use this with a ByteString at native speeds, and a [Word8] at 
its native speed.

But this doesn't buy us the ability to use this library interchangably with a 
Word8-based ByteString and a [Char].  That is a scenario ListLike is not 
designed to help with.  ListLike is designed to make the container 
interchangable, but does not address making the contents interchangable.

I think this is what you are pointing out?

 your favourite representation on the edge. So in this case those
 conversions would be pack/unpack or the similar equivalents for strict
 - lazy bytestrings.

 If we want it to be generic then we want a class of string like things
 that provides conversions only, not operations.

 For example we could export iconv as:

 iconv :: StringLike string = Encoding - Encoding - string - string
 iconv to from = (convertStringRep :: Lazy.ByteString - string)
   . theRealIconv
   . (convertStringRep :: string - Lazy.ByteString)

 class StringLike string where
   ...

 convertStringRep :: (StringLike s1, StringLike s2) = s1 - s2
 -- analogous to fromIntegral

ListLike has something along these lines, too: [1]

class StringLike s where
  toString :: s - String
  fromString :: String - s
  lines :: ListLike full s = s - full
  words :: ListLike full s = s - full
  unlines :: ListLike full s = full - s
  unwords :: ListLike full s = full - s

The last four functions are there as a way to provide a universal interface 
to optimized native functions, where available.  The minimal complete 
definition is just toString and fromString.

Technically, you could make every function look like:

iconv data = fromString . toString $ realIConv (fromString . toString $ data)

That can be made simpler for the programmer with a helper function, but is 
not necessarily very efficient.  With an MPTC, we could do:

class StringConvertable s1 s2 where
convertString :: s1 - s2
withString :: s1 - (s2 - a) - a
withString x func = func (convertString x)

interactString :: s1 - (s2 - s2) - s1
interactString x func = convertString (func (convertString x)

which ought to make easy conversions (String to ByteString, for instance) 
easily doable for a library such as iconv.  What do you think?

[1] 
http://software.complete.org/listlike/static/doc/ListLike/Data-ListLike-String.html#t%3AStringLike

[2] 
http://software.complete.org/listlike/static/doc/ListLike/Data-ListLike-IO.html



 Duncan


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


Re: [Haskell-cafe] Selecting Array type

2008-02-20 Thread Ryan Ingram
Oleg's done a lot of work here; there's a bunch of magic that can be
done with TypeCast.  I took my inspiration from here:
http://okmij.org/ftp/Haskell/typecast.html#ambiguity-resolution

Here are some tests in ghci (note that I specialized the index type in
test to Int to make this shorter; doing so isn't technically
required):
Prelude SmartArray :t test (1::Int)
test (1::Int) :: Data.Array.Base.UArray Int Int
Prelude SmartArray :t test (1::Int, 2::Int)
test (1::Int, 2::Int) :: GHC.Arr.Array Int (Int, Int)
Prelude SmartArray :t test Foo
test Foo :: GHC.Arr.Array Int [Char]
Prelude SmartArray :t test False
test False :: Data.Array.Base.UArray Int Bool
Prelude SmartArray

The trick is to represent whether a type is boxed or not via a
type-level boolean, which you can then use to affect the instance
selecton.  Here is the source:


{-# OPTIONS_GHC
   -fglasgow-exts
   -fbreak-on-exception
   -fallow-undecidable-instances
   -fallow-overlapping-instances
#-}
module SmartArray where
import Data.Ix
import Data.Array.Unboxed
import Data.Complex

type SmartArray i e = (Ix i, SmartArraySelector a e) = (a i e)

-- smartArray is similar to array function from Data.Array. But, it
-- will return a UArray if e can be unboxed.  Otherwise, it returns an Array.

smartArray :: (i, i) - [(i, e)] - SmartArray i e
smartArray bnd eLst = array bnd eLst

class (IArray a e) = SmartArraySelector a e | e - a

-- SmartArraySelector selects UArray for all types that can be
-- unboxed.  An instance has to be created for each unboxed type.  I'd
-- like to avoid listing all unboxed types here.  However, since there
-- are only a few unboxed types, it's not too burdensome to list them
-- all.  (For brevity, I didn't create all possible instances.)

class IsUnboxed t b | t - b

instance TypeCast b HTrue = IsUnboxed Bool b
instance TypeCast b HTrue = IsUnboxed Char b
instance TypeCast b HTrue = IsUnboxed Double b
instance TypeCast b HTrue = IsUnboxed Float b
instance TypeCast b HTrue = IsUnboxed Int b
instance TypeCast b HFalse = IsUnboxed a b   -- overlap here

class IArray a t = ArraySelector b t a | b t - a
   -- where array' :: Ix i = b - (i,i) - [(i,t)] - a i t

instance IArray UArray a = ArraySelector HTrue  a UArray -- where
array' _ = array
instance ArraySelector HFalse a Array -- where array' _ = array

instance (IsUnboxed t b, ArraySelector b t a) = SmartArraySelector a t

test :: SmartArraySelector a e = e - a Int e
test e = smartArray (0,10) [ (i,e) | i - [0..10]]



-- Magic toolbox that solves everything!  Thanks Oleg!

data HTrue
data HFalse

class TypeCast   a b   | a - b, b-a   where typeCast   :: a - b
class TypeCast'  t a b | t a - b, t b - a where typeCast'  :: t-a-b
class TypeCast'' t a b | t a - b, t b - a where typeCast'' :: t-a-b
instance TypeCast'  () a b = TypeCast a b where typeCast x = typeCast' () x
instance TypeCast'' t a b = TypeCast' t a b where typeCast' = typeCast''
instance TypeCast'' () a a where typeCast'' _ x  = x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] stream/bytestring questions

2008-02-20 Thread Roman Leshchinskiy

Chad Scherrer wrote:


Here's an example of the problem. Start with a function

extract :: [Int] - [a] - [a]
extract = f 0
where
f !k nss@(n:ns) (x:xs)
  | n == k= x : f (k+1) ns xs
  | otherwise = f (k+1) nss xs
f _ _ _ = []


If you want this to play nicely with stream fusion, you have to define a 
version of extract which works on streams instead of lists:


extractS :: Stream Int - Stream a - Stream a

Now, you can easily define a fusible list version:

extract ns xs = unstream (extractS (stream ns) (stream xs))

In general, I don't see why programming directly with streams is 
something that should be avoided. You do have to be quite careful, 
though, if you want to get good performance (but GHC's simplifier is 
becoming increasingly robust in this respect).



extract ns xs == [xs !! n | n - ns]


Note that in contrast to your function, this doesn't assume that ns is 
sorted and hence, there is no way to implement this without producing an 
intermediate list.


Roman

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


Re: [Haskell-cafe] question about STM and IO

2008-02-20 Thread Ryan Ingram
On 2/20/08, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 STM operations can be repeated if first transaction was unsuccessful.
 so, you may se here only operations that may be safely repeated - say,
 reading/writing memory areas, or reading/writing files, or even
 sending network message as long as its duplication is ok

Actually, you have to be even more careful than that; you may only
include not just operations that may be safely repeated, but
operations that may be erroneously executed.  Consider the following
snippet:

badNews:: TVar Int - TVar Int - IO ()
badNews xRef yRef = atomically $ do
x - xRef
y - yRef
if (x  y) then unsafeIOToSTM launchMissiles else return ()

(where launchMissiles has serious side effects, but can be called
repeatedly without problem; the missiles will already have been
launched in the second call).

Even if (x  y) is never atomically true, launchMissiles could get
executed during the evaluation of this STM action if it was run
concurrently with another action that wrote new values to x and y in
some order, such as the following snippet

safe :: TVar Int - TVar Int - IO ()
safe xRef yRef = do
atomically $ do
 writeTVar xRef 15
 writeTVar yRef 13

main :: IO ()
main = do
xRef - newTVar 10
yRef - newTVar 8
forkIO safe
forkIO badNews

If badNews runs to the point of reading from xRef, then safe runs
in its entirety and commits successfully, then badNews resumes,
launchMissiles will get called and then badNews will fail to commit
and be restarted.  The second runthrough of badNews will read the
values, determine that x = y, and just return (), but it's too late,
the missiles have already been launched.

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


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Roman Leshchinskiy

John Goerzen wrote:


I am concerned that the same thing is happening in Haskell.  We know
have three common list-like types: the regular list, strict
ByteString, and lazy ByteString.


Why do you consider ByteString to be list-like but not arrays?


1) Does everyone agree with me that we have a problem here?


Yes, definitely. Haskell simply lacks a standard container library.


2) Would it make sense to make ListLike, or something like it,
   part of the Haskell core?


I don't think ListLike is the right approach. It's basically a fairly 
arbitrary collection of functions. It would be preferable, IMO, to 
identify a small set of combinators which would allow most list/sequence 
functions to be implemented generically and efficiently. Personally, I'd 
go with something like streams (the stream fusion ones) but I'm biased, 
of course.



3) Would it make sense to base as much code as possible in the Haskell
   core areound ListLike definitions?  Here I think of functions such
   as lines and words, which make sense both on [Char] as well as
   ByteStrings.


Yes, as long as there are only very few core combinators. The more 
methods your ListLike class has, the harder it is to justify why a new 
function should be implemented in terms of those and not included in the 
class.



4) We are missing one final useful type: a Word32-based ByteString.
   When working in the Unicode character set, a 32-bit character
   can indeed be useful, and I could see situations in which the
   performance benefit of a ByteString-like implementation could
   be useful combared to [Char].


I have to disagree somewhat. What we are missing is a nice, efficient 
array library. There is nothing magical about ByteStrings, they are just 
unboxed arrays. In fact, there is no good reason for ByteString to be a 
   separate type at all.


Roman

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


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Ryan Ingram
It depends what you mean by faster; more efficient (runtime) or less
typing (programmer time!)

For the former, you have basically the best implementation there is;
you are basically encoding the continuation of (++) into the
accumulating list of arguments to evs.  You might want to consider
difference lists to simplify the definition, however; the performance
should be comparable:

newtype DList a = DL ([a] - [a])

dlToList :: DList a - [a]
dlToList (DL l) = l []

dlSingleton :: a - DList a
dlSingleton = DL . (:)

dlConcat :: DList a - DList a - DList a
dlConcat (DL l1) (DL l2) = DL (l1 . l2)

varsDL :: Prp a - DList a
varsDL (Var a) = dlSingleton a
varsDL (Not a) = varsDL a
varsDL (Or a b) = varsDL a `dlConcat` varsDL b
-- etc.

If you want less typing, consider some form of generics programming
such as using Scrap your Boilerplate; see
http://www.cs.vu.nl/boilerplate/

data Prp a = ... deriving (Eq, Show, Data, Typeable)

-- note that this gives the wrong result for Prp Bool because of Cns.
-- this is fixable, see http://www.cs.vu.nl/boilerplate/testsuite/foldTree.hs
varsGeneric :: forall a. Typeable a = Prp a - [a]
varsGeneric = listify (\x - case (x :: a) of _ - True)

  -- ryan

On 2/20/08, Cetin Sert [EMAIL PROTECTED] wrote:
 -- proposition
 data Prp a = Var a
| Not (Prp a)
| Or  (Prp a) (Prp a)
| And (Prp a) (Prp a)
| Imp (Prp a) (Prp a)
| Xor (Prp a) (Prp a)
| Eqv (Prp a) (Prp a)
| Cns Bool
deriving (Show, Eq)

 -- Here are to variable extraction methods

 -- variable extraction reference imp.
 -- Graham Hutton: Programming in Haskell, 107
 vars_ :: Prp a → [a]
 vars_ (Cns _)   = []
 vars_ (Var x)   = [x]
 vars_ (Not p)   = vars_ p
 vars_ (Or  p q) = vars_ p ++ vars_ q
 vars_ (And p q) = vars_ p ++ vars_ q
 vars_ (Imp p q) = vars_ p ++ vars_ q
 vars_ (Xor p q) = vars_ p ++ vars_ q
 vars_ (Eqv p q) = vars_ p ++ vars_ q

 -- variable extraction new * this is faster
 vars :: Prp a → [a]
 vars p = evs [p]
   where
 evs []   = []
 evs (Cns _  :ps) = []
 evs (Var x  :ps) = x:evs ps
 evs (Not p  :ps) = evs (p:ps)
 evs (Or  p q:ps) = evs (p:q:ps)
 evs (And p q:ps) = evs (p:q:ps)
 evs (Imp p q:ps) = evs (p:q:ps)
 evs (Xor p q:ps) = evs (p:q:ps)
 evs (Eqv p q:ps) = evs (p:q:ps)

 -- for  : Not (Imp (Or (Var 'p') (Var 'q')) (Var p))
 -- vars_: ['p','q','p']
 -- vars : ['p','q','p']

 -- order and the fact that 'p' appears twice being irrelevant:
 -- is there an even faster way to do this?
 --
 -- Cetin Sert
 -- www.corsis.de

 ___
 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] A little toy of Haskell Trivia

2008-02-20 Thread Benjamin L. Russell
Rewriting that script in Haskell could be an
interesting exercise.  Do you have the source code?

Benjamin L. Russell

--- Steve Lihn [EMAIL PROTECTED] wrote:

 I proudly announce a little toy that lists the
 frequency of modules
 being imported by other modules. Do you know
 Control.Monad is the most
 frequently imported module? I did not!
 
 Currently it only includes GHC 6.8 core library. If
 you have any idea
 how to parse through HackageDB code, please let me
 know.
 
 http://haskell.ecoin.net/cgi-bin/modules.pl
 
 Disclaimer: This is entirely for fun. It is by no
 means accurate or
 complete. I only spent a couple hours on a little
 perl script and a
 mysql table...
 ___
 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] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb

G'day all.

Quoting Cetin Sert [EMAIL PROTECTED]:


-- proposition
data Prp a = Var a
   | Not (Prp a)
   | Or  (Prp a) (Prp a)
   | And (Prp a) (Prp a)
   | Imp (Prp a) (Prp a)
   | Xor (Prp a) (Prp a)
   | Eqv (Prp a) (Prp a)
   | Cns Bool
   deriving (Show, Eq)


This is probably the fastest:

vars :: Prp a - [a]
vars p = vars' p []
  where
vars' (Var a) = (a:)
vars' (Not p) = vars' p
vars' (Or l r) = vars' l . vars' r
{- etc -}
vars' (Cns _) = id

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


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread ajb

G'day all.

Quoting Neil Mitchell [EMAIL PROTECTED]:


Yes, its the projection onto another type:

[] = Nothing
(x:xs) = Just (x, xs)


Also known as msplit:

http://www.haskell.org/haskellwiki/New_monads/MonadSplit

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


[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Henning Thielemann

On Wed, 20 Feb 2008, Chad Scherrer wrote:

 On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote:
  For anyone looking into it - the StorableVector fusion would have to
  be quite different from the current ByteString fusion framework.
  Maybe it would be enough to lay down a Stream fusion framework for
  StorableVectors.

 I must be missing something. Why would it have to be so different?

I think there can also be problems simply because the element type is no
longer fixed to Word8 but also not entirely free, but restricted to
Storable. E.g. you cannot simply replace
SV.fromList . List.map f by  SV.map f . SV.fromList
 because in the second form not only the result type of 'f' must be
Storable, but the input type of 'f' must be Storable, too.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Henning Thielemann

On Thu, 21 Feb 2008, Roman Leshchinskiy wrote:

 John Goerzen wrote:

  2) Would it make sense to make ListLike, or something like it,
 part of the Haskell core?

 I don't think ListLike is the right approach. It's basically a fairly
 arbitrary collection of functions. It would be preferable, IMO, to
 identify a small set of combinators which would allow most list/sequence
 functions to be implemented generically and efficiently. Personally, I'd
 go with something like streams (the stream fusion ones) but I'm biased,
 of course.

As long as it is only about speeding up list processing, one might also
consider this as optimization problem. This could be handled without
adapting much List based code in applications to a generic sequence class.
That is, if I convert the result of a composition of list functions to a
lazy ByteString, I tell the compiler that I don't need full laziness and
the compiler can optimize, say
   ByteString.fromList . List.func1 . List.func2 . List.build
 to
   ByteString.func1 . ByteString.func2 . ByteString.build
 or even better
   ByteString.fusedFunc1Func2Build
 by some clever fusion framework. I think that a type class is easier to
justify if it unifies data structures that are more different than just
providing the same API with different efficiency.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
plong 0 = Var 0
plong n | even n= Or  (Var n) (plong (n-1))
| otherwise = And (Var n) (plong (n-1))

main = do print ((length ∘ vars) (plong 1000))
real0m3.290s
user0m3.152s
sys 0m0.020s

main = do print ((length ∘ vars_) (plong 1000))
real0m3.732s
user0m3.680s
sys 0m0.024s

-- vrsn=varsBromage
main = do print ((length ∘ vrsn) (plong 1000))
real0m4.164s
user0m4.128s
sys 0m0.008s

ghc -fglasgow-exts -O2
ghc 6.8.2

@Andrew:
It is astonishing to see that your version actually performs the worst (at
least on my machine). By looking at your code I had also thought that yours
would be the fastest in terms of runtime performance, it was also exactly
what I tried but failed to get to here on my own. Maybe future ghc versions
will change this in favour of your version.

I would like to have someone test it on another machine though:

fetch: svn co https://okitsune.svn.sourceforge.net/svnroot/okitsune .
build: ghc -fglasgow-exts -O2 Common.hs Propositions.hs Test.hs
testS: time ./a.out sert
testH: time ./a.out hutton
testB: time ./a.out bromage

Best regards,
Cetin Sert.

On 21/02/2008, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

 G'day all.


 Quoting Cetin Sert [EMAIL PROTECTED]:

  -- proposition
  data Prp a = Var a
 | Not (Prp a)
 | Or  (Prp a) (Prp a)
 | And (Prp a) (Prp a)
 | Imp (Prp a) (Prp a)
 | Xor (Prp a) (Prp a)
 | Eqv (Prp a) (Prp a)
 | Cns Bool
 deriving (Show, Eq)


 This is probably the fastest:

 vars :: Prp a - [a]
 vars p = vars' p []
where
  vars' (Var a) = (a:)

  vars' (Not p) = vars' p

  vars' (Or l r) = vars' l . vars' r
  {- etc -}
  vars' (Cns _) = id

 Cheers,
 Andrew Bromage

 ___
 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] question about STM and IO

2008-02-20 Thread John Lato
I take it that this follows from the lack of any mechanism to rollback
IO?  If so, I think that the following guidelines suffice for when
it's acceptable to use unsafeIOtoSTM:

1.  The IO action must be able to be safely repeated.
2.  The IO action must be able to be safely performed with
possibly-incorrect arguments, even if it isn't supposed to be
performed.
3.  Don't try to nest transactions.

If I understand it correctly, I think that covers it.
Thanks to everyone who answered; I really appreciate it.
John

On Wed, Feb 20, 2008 at 8:02 PM, Ryan Ingram [EMAIL PROTECTED] wrote:
 On 2/20/08, Bulat Ziganshin [EMAIL PROTECTED] wrote:
   STM operations can be repeated if first transaction was unsuccessful.
   so, you may se here only operations that may be safely repeated - say,
   reading/writing memory areas, or reading/writing files, or even
   sending network message as long as its duplication is ok

  Actually, you have to be even more careful than that; you may only
  include not just operations that may be safely repeated, but
  operations that may be erroneously executed.  Consider the following
  snippet:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Henning Thielemann

On Thu, 21 Feb 2008, Wolfgang Jeltsch wrote:

 Am Mittwoch, 20. Februar 2008 22:22 schrieb Steve Lihn:
  I proudly announce a little toy that lists the frequency of modules
  being imported by other modules. Do you know Control.Monad is the most
  frequently imported module? I did not!

 This doesn’t surprise me very much.  What surprises me more is that OpenGL
 stuff is that popular. :-)

Maybe some kind of self-citation ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Derek Elkins
On Thu, 2008-02-21 at 05:10 +0100, Cetin Sert wrote:
 plong 0 = Var 0
 plong n | even n= Or  (Var n) (plong (n-1))
 | otherwise = And (Var n) (plong (n-1))

compare the times again but with plong as follows:
plong 0 = Var 0
plong n | even n = Or (plong (n-1)) (Var n)
| otherwise = And (plong (n-1)) (Var n)

  
 
 main = do print ((length ∘ vars) (plong 1000))
 real0m3.290s
 user0m3.152s
 sys 0m0.020s
 
 main = do print ((length ∘ vars_) (plong 1000))
 real0m3.732s
 user0m3.680s
 sys 0m0.024s
 
 -- vrsn=varsBromage
 main = do print ((length ∘ vrsn) (plong 1000))
 real0m4.164s
 user0m4.128s
 sys 0m0.008s
 
 ghc -fglasgow-exts -O2
 ghc 6.8.2
 
 @Andrew:
 It is astonishing to see that your version actually performs the worst
 (at least on my machine). By looking at your code I had also thought
 that yours would be the fastest in terms of runtime performance, it
 was also exactly what I tried but failed to get to here on my own.
 Maybe future ghc versions will change this in favour of your version.
 
 I would like to have someone test it on another machine though:
 
 fetch: svn co https://okitsune.svn.sourceforge.net/svnroot/okitsune .
 build: ghc -fglasgow-exts -O2 Common.hs Propositions.hs Test.hs
 testS: time ./a.out sert
 testH: time ./a.out hutton
 testB: time ./a.out bromage
 
 
 Best regards,
 Cetin Sert.
 
 On 21/02/2008, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:
 G'day all.
 
 
 Quoting Cetin Sert [EMAIL PROTECTED]:
 
  -- proposition
  data Prp a = Var a
 | Not (Prp a)
 | Or  (Prp a) (Prp a)
 | And (Prp a) (Prp a)
 | Imp (Prp a) (Prp a)
 | Xor (Prp a) (Prp a)
 | Eqv (Prp a) (Prp a)
 | Cns Bool
 deriving (Show, Eq)
 
 
 This is probably the fastest:
 
 vars :: Prp a - [a]
 vars p = vars' p []
where
  vars' (Var a) = (a:)
 
  vars' (Not p) = vars' p
 
  vars' (Or l r) = vars' l . vars' r
  {- etc -}
  vars' (Cns _) = id
 
 Cheers,
 Andrew Bromage
 
 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On Wednesday 20 February 2008 8:42:56 pm Roman Leshchinskiy wrote:
 John Goerzen wrote:
  I am concerned that the same thing is happening in Haskell.  We know
  have three common list-like types: the regular list, strict
  ByteString, and lazy ByteString.

 Why do you consider ByteString to be list-like but not arrays?

  1) Does everyone agree with me that we have a problem here?

 Yes, definitely. Haskell simply lacks a standard container library.

  2) Would it make sense to make ListLike, or something like it,
 part of the Haskell core?

 I don't think ListLike is the right approach. It's basically a fairly
 arbitrary collection of functions. It would be preferable, IMO, to
 identify a small set of combinators which would allow most list/sequence
 functions to be implemented generically and efficiently. Personally, I'd
 go with something like streams (the stream fusion ones) but I'm biased,
 of course.

From what I've heard of streams in this discussion, that does sound quite 
interesting.  Unless streams are used internally for the [] implementation, 
though, we'd still need something to resolve the library compatibility 
question.

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


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb

G'day all.

Quoting Cetin Sert [EMAIL PROTECTED]:


It is astonishing to see that your version actually performs the worst (at
least on my machine).


On your example, I'm not surprised:


plong 0 = Var 0
plong n | even n= Or  (Var n) (plong (n-1))
| otherwise = And (Var n) (plong (n-1))


This is effectively a singly linked list.  I would expect my (well, I
didn't invent it) to work better on something that didn't have this
unique structure, such as:

test 0 = Var 0
test n | even n= Or  (Var n) (test (n-1))
   | otherwise = And (test (n-1)) (Var n)

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


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m1.384s
user0m1.148s
sys 0m0.112s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m2.240s
user0m1.972s
sys 0m0.176s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
1001

real0m59.875s
user0m58.080s
sys 0m1.656s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
1001

real0m32.043s
user0m30.930s
sys 0m0.992s


Hutton seems to fail miserably in both lengths here o_O

I was not aware of the effect of structures on performance.
Thanks for reminding me!

Best Regards,
Cetin Sert

On 21/02/2008, Derek Elkins [EMAIL PROTECTED] wrote:

 On Thu, 2008-02-21 at 05:10 +0100, Cetin Sert wrote:
  plong 0 = Var 0
  plong n | even n= Or  (Var n) (plong (n-1))
  | otherwise = And (Var n) (plong (n-1))


 compare the times again but with plong as follows:
 plong 0 = Var 0
 plong n | even n = Or (plong (n-1)) (Var n)
 | otherwise = And (plong (n-1)) (Var n)


 
 
  main = do print ((length ∘ vars) (plong 1000))
  real0m3.290s
  user0m3.152s
  sys 0m0.020s
 
  main = do print ((length ∘ vars_) (plong 1000))
  real0m3.732s
  user0m3.680s
  sys 0m0.024s
 
  -- vrsn=varsBromage
  main = do print ((length ∘ vrsn) (plong 1000))
  real0m4.164s
  user0m4.128s
  sys 0m0.008s
 
  ghc -fglasgow-exts -O2
  ghc 6.8.2
 
  @Andrew:
  It is astonishing to see that your version actually performs the worst
  (at least on my machine). By looking at your code I had also thought
  that yours would be the fastest in terms of runtime performance, it
  was also exactly what I tried but failed to get to here on my own.
  Maybe future ghc versions will change this in favour of your version.
 
  I would like to have someone test it on another machine though:
 
  fetch: svn co https://okitsune.svn.sourceforge.net/svnroot/okitsune .
  build: ghc -fglasgow-exts -O2 Common.hs Propositions.hs Test.hs
  testS: time ./a.out sert
  testH: time ./a.out hutton
  testB: time ./a.out bromage
 
 
  Best regards,
  Cetin Sert.
 
  On 21/02/2008, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:
  G'day all.
 
 
  Quoting Cetin Sert [EMAIL PROTECTED]:
 
   -- proposition
   data Prp a = Var a
  | Not (Prp a)
  | Or  (Prp a) (Prp a)
  | And (Prp a) (Prp a)
  | Imp (Prp a) (Prp a)
  | Xor (Prp a) (Prp a)
  | Eqv (Prp a) (Prp a)
  | Cns Bool
  deriving (Show, Eq)
 
 
  This is probably the fastest:
 
  vars :: Prp a - [a]
  vars p = vars' p []
 where
   vars' (Var a) = (a:)
 
   vars' (Not p) = vars' p
 
   vars' (Or l r) = vars' l . vars' r
   {- etc -}
   vars' (Cns _) = id
 
  Cheers,
  Andrew Bromage
 
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
 I would expect my (well, I didn't invent it) to work better on something
that didn't have this unique structure, such as:
 test 0 = Var 0
 test n | even n= Or  (Var n) (test (n-1))
   | otherwise = And (test (n-1)) (Var n)

for some reason this still does not perform as well as it should o__O
I think function composition might somehow be the bottleneck behind this.

--with
plong 0 = Var 0
plong n | even n= Or  (Var n) (plong (n-1))
| otherwise = And (plong (n-1)) (Var n)

--and n = 100

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m0.692s
user0m0.624s
sys 0m0.040s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m0.696s
user0m0.644s
sys 0m0.036s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m0.840s
user0m0.744s
sys 0m0.052s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m1.561s
user0m1.360s
sys 0m0.100s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m1.692s
user0m1.392s
sys 0m0.136s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m1.959s
user0m1.580s
sys 0m0.116s

Best Regards,
Cetin Sert

On 21/02/2008, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

 G'day all.

 Quoting Cetin Sert [EMAIL PROTECTED]:


  It is astonishing to see that your version actually performs the worst
 (at
  least on my machine).


 On your example, I'm not surprised:


  plong 0 = Var 0
  plong n | even n= Or  (Var n) (plong (n-1))
  | otherwise = And (Var n) (plong (n-1))


 This is effectively a singly linked list.  I would expect my (well, I
 didn't invent it) to work better on something that didn't have this
 unique structure, such as:

 test 0 = Var 0
 test n | even n= Or  (Var n) (test (n-1))
 | otherwise = And (test (n-1)) (Var n)


 Cheers,
 Andrew Bromage
 ___
 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] Selecting Array type

2008-02-20 Thread Jeff φ
On 2/19/08, Ryan Ingram [EMAIL PROTECTED] wrote:

 Oleg's done a lot of work here; there's a bunch of magic that can be
 done with TypeCast.  I took my inspiration from here:
 http://okmij.org/ftp/Haskell/typecast.html#ambiguity-resolution


 . . .


The trick is to represent whether a type is boxed or not via a
 type-level boolean, which you can then use to affect the instance
 selecton.


 . . .



 -- Magic toolbox that solves everything!  Thanks Oleg!

 data HTrue
 data HFalse

 class TypeCast   a b   | a - b, b-a   where typeCast   :: a - b
 class TypeCast'  t a b | t a - b, t b - a where typeCast'  :: t-a-b
 class TypeCast'' t a b | t a - b, t b - a where typeCast'' :: t-a-b
 instance TypeCast'  () a b = TypeCast a b where typeCast x = typeCast' ()
 x
 instance TypeCast'' t a b = TypeCast' t a b where typeCast' = typeCast''
 instance TypeCast'' () a a where typeCast'' _ x  = x


Thanks for showing me this technique.  I studied your code for several
hours.  And, I've read Oleg's Strongly Typed Heterogeneous Collections.

As a learning exercise, I modified your code.  I managed to shorten it a
bit, but I had a couple of surprises.  Please see my comments in the code
below.

{-# OPTIONS_GHC
   -fglasgow-exts
   -fbreak-on-exception
   -fallow-undecidable-instances
   -fallow-overlapping-instances
#-}
module SmartArray where

import IO
import Data.Ix
import Data.Array.Unboxed
import Data.Complex

type SmartArray i e = (Ix i, SmartArraySelector a e) = (a i e)

-- smartArray is similar to array function from Data.Array. But,
-- it will return a UArray if e can be unboxed.  Otherwise, it
-- returns an Array.

smartArray :: (i, i) - [(i, e)] - SmartArray i e
smartArray bnd eLst = array bnd eLst

class ArrTypeCast a b | a - b, b-a where
arrTypeCast :: a i e - b i e

instance ArrTypeCast x x where
arrTypeCast = id

-- SURPRISE 1: If function, arrTypeCast, is removed, (from both
-- the class and instance) GHC assumes the kind of a and b are *,
-- instead of * - * - * and produce . . .
--
-- report3.hs:37:24:
-- `UArray' is not applied to enough type arguments
-- Expected kind `*', but `UArray' has kind `* - * - *'
-- In the type `(ArrTypeCast a UArray, IArray a Bool) =
--  SmartArraySelector a Bool'
-- In the instance declaration for `SmartArraySelector a Bool'
--
-- It appears that functions defined in a class can constrain the
-- type variables of the class.  To me, this seems a bit magical
-- and unexpected.

class (IArray a e) = SmartArraySelector a e | e - a

-- instances of SmartArraySelector for all boxed types (For
-- breivity, not all unboxed types are listed.)

instance (ArrTypeCast a UArray, IArray a Bool)
= SmartArraySelector a Bool
instance (ArrTypeCast a UArray, IArray a Char)
= SmartArraySelector a Char
instance (ArrTypeCast a UArray, IArray a Double)
= SmartArraySelector a Double
instance (ArrTypeCast a UArray, IArray a Float)
= SmartArraySelector a Float
instance (ArrTypeCast a UArray, IArray a Int)
= SmartArraySelector a Int

-- SURPRISE 2: The class SmartArraySelector has the type
-- assertion, (IArray a e).  It seems like adding an additional
-- IArray assertion to each instance is redundant.  However,
-- if I remove the assertion (IArray a Int) above, GHC
-- reports . . .
-- 
-- report3.hs:37:24:
-- `UArray' is not applied to enough type arguments
-- Expected kind `*', but `UArray' has kind `* - * - *'
-- In the type `(ArrTypeCast a UArray, IArray a Bool) =
--  SmartArraySelector a Bool'
-- In the instance declaration for `SmartArraySelector a Bool'
--
-- Why is this second type assertion required?


instance (ArrTypeCast a Array, IArray a b)
= SmartArraySelector a b


test :: SmartArraySelector a e = e - a Int e
test e = smartArray (0,10) [ (i,e) | i - [0..10]]

I'd love to find a good article that describes the ins and outs of multi
parameter types, functional dependencies, and type assertions, in enough
detail to resolve these surprises.  A step-by-step walk through showing how
the compiler resolve a type and selects an instance would be awesome.

Usually, when I'm having trouble getting Haskell's type system to do what I
want, I resort to trial and error tactics.  I wish I had a better foundation
so I could take a more intelligent approach to type hacking.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread David Menendez
On Wed, Feb 20, 2008 at 10:46 PM,  [EMAIL PROTECTED] wrote:
  Quoting Neil Mitchell [EMAIL PROTECTED]:

   Yes, its the projection onto another type:
  
   [] = Nothing
   (x:xs) = Just (x, xs)

  Also known as msplit:

  http://www.haskell.org/haskellwiki/New_monads/MonadSplit

Almost. The projection has type f a - Maybe (a, f a), but msplit has
type f a - f (Maybe (a, f a)).

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe