Re: [Haskell-cafe] Fwd: [Haskell-beginners] Monad instances and type synonyms

2013-04-14 Thread Steffen Schuldenzucker


The point in not allowing partially applied type synonym instances is 
that it'd make deciding whether a type is an instance of a class much 
harder.

Cf. here[1] for a similar question with the Category class.

-- Steffen

[1] Attached message. Couldn't find it on the archives..

On 04/14/2013 07:10 AM, Christopher Howard wrote:


I asked this question in Haskell-beginners, but I haven't heard anything
yet, so I'm forwarding to Cafe.

 Original Message 
Subject: [Haskell-beginners] Monad instances and type synonyms
Date: Sat, 13 Apr 2013 17:03:57 -0800
From: Christopher Howardchristopher.how...@frigidcode.com
Reply-To: The Haskell-Beginners Mailing List - Discussion of primarily
beginner-level topics related to Haskellbeginn...@haskell.org
To: Haskell Beginnersbeginn...@haskell.org

I am playing around with some trivial code (for learning purposes) I
wanted to take

code:

-- SaleVariables a concrete type defined early

-- `Adjustment' represents adjustment in a price calculation
-- Allows functions of type (a -  Adjustment a) to be composed
-- with an appropriate composition function
type Adjustment a = SaleVariables -  a


And put it into

code:

instance Monad Adjustment where

   (=) = ...
   return = ...


If I try this, I get

code:

Type synonym `Adjustment' should have 1 argument, but has been given none
In the instance declaration for `Monad Adjustment'


But if I give an argument, then it doesn't compile either (it becomes a
* kind). And I didn't want to make the type with a regular data
declaration either, because then I have to give it a constructor, which
doesn't fit with what I want the type to do.




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


---BeginMessage---


Hi Markus,

On 07/06/2011 03:04 PM, Markus Läll wrote:

[...]

import Control.Arrow
import Control.Category

type X a b = [a] -  [b]

instance Category X where
id = map Prelude.id
g . f = g Prelude.. f

instance Arrow X where
arr f = map f
first f = unzip  first f  uncurry zip

The problem is that it's not allowed to use partially applied type
synonyms. It is however possible to define a type synonym which value
is a partially applied type, but I haven't been able to figure out if
I could somehow use that fact in defining the X... Is it at all
possible, or is a newtype the only way to do it?



You should really use a newtype for that. Allowing partially applied 
type synonyms would greatly increase the expressiveness of the type 
language. (too much, actually)

In fact, you could write arbitrary type level lambdas, like that:

 type Y b a = [a] - [b]

But now, given instances like this:

 instance Category X where ...

 instance Category Y where ...
 -- uh, yeah, does it make sense in this case? Whatever, we *could* 
have an instance.


, any function of type [a] - [b] will match both instances. So which 
instance to choose? We have two solutions:


a) The compiler discovers itself that we have overlaps here and complains.

This seems hard to me (is it even possible in finite time?). Note that 
it is easy if type synonyms are always fully applied because the 
compiler just has to fill in the definition of all the types and can 
then proceed to compare just the instance *heads*.


b) You somehow annotate which instance to choose for each specific case. 
But that's exactly what newtypes are for!


The problem does indeed occur in your example: What is (id :: [a] - 
[b]) supposed to be, Prelude.id (as given by the general instance for 
functions) or map Prelude.id (given by your instance)?


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


Re: [Haskell-cafe] code-as-config, run-time checks and error locations

2013-04-07 Thread Steffen Schuldenzucker


This one[1] sounds so awesome! I just read the paper.
In particular I like how one could access the current call stack 
structure live.


However, the most recent changes to the code are from early 2009.
Anyone knows what happened to this?

[1] 
http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack/CorePassImplementation


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


[Haskell-cafe] code-as-config, run-time checks and error locations

2013-04-06 Thread Steffen Schuldenzucker

Dear Café,

I'm working on a EDSL that will include both type checks (at compile
time) and semantic checks (at run time). - Semantic properties are known
at compile time but feel too complex to me to be encoded in the type system.

If one of the runtime checks fails, I'd like to print the location of 
the error, i.e. not

  Error: Unknown field `AMOUNT' in table `ENTRIES'
(where? why?)
but
  Error: Unknown field `AMOUNT' in table `ENTRIES'
  Referenced at analysis1.hs:43:7 by `sumByInvoice'
which was called at analysis1.hs:66:3 by `main'
  ENTRIES defined at analysis1.hs:13:8

I'm not yet sure which level of granularity I want for error messages
and one can probably get arbitrarily fancy on this.
For the moment I think it would be enough to auto-insert the location of
calls to a certain set of functions.

Any experience on this?

Thanks a lot.
-- Steffen


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


Re: [Haskell-cafe] code-as-config, run-time checks and error locations

2013-04-06 Thread Steffen Schuldenzucker


Good Point!
Doesn't quite meet my requirements (I don't want to show the error loc 
somewhere deep within the libs), but it led me here[1].

Reading through that now...

[1] http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack

On 04/06/2013 07:51 PM, Kim-Ee Yeoh wrote:

On Sun, Apr 7, 2013 at 12:23 AM, Steffen Schuldenzucker
sschuldenzuc...@uni-bonn.de  wrote:

For the moment I think it would be enough to auto-insert the location of
calls to a certain set of functions.


Have you tried assert [1]?

[1] 
http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Control-Exception.html#v:assert

-- Kim-Ee



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


Re: [Haskell-cafe] monoid pair of monoids?

2012-12-21 Thread Steffen Schuldenzucker


Hi Christopher,

On 12/21/2012 09:27 AM, Christopher Howard wrote:

[...]
Of course, I thought it would be likely I would want other classes and
instances with additional numbers of types:

code:

data Socket3 a b c = Socket3 a b c
   deriving (Show)

instance (Monoid a, Monoid b, Monoid c) =  Monoid (Socket3 a b c) where
 mempty = Socket3 mempty mempty mempty
 Socket3 a b c `mappend` Socket3 w x y =
 Socket3 (a `mappend` w) (b `mappend` x) (c `mappend` y)

data Socket4 a b c d = Socket4 a b c d
   deriving (Show)

instance (Monoid a, Monoid b, Monoid c, Monoid d) =  Monoid (Socket4 a b
c d) where
 mempty = Socket4 mempty mempty mempty mempty
 Socket4 a b c d `mappend` Socket4 w x y z =
 Socket4 (a `mappend` w) (b `mappend` x) (c `mappend` y) (d
`mappend` z)

data Socket 5 a b c d e... et cetera


Seeing as the pattern here is so rigid and obvious, I was wondering: is
it possible to abstract this even more? So I could, for instance, just
specify that I want a Socket with 8 types, and poof, it would be there?
Or is this as meta as we get? (I.e., without going to something like
Template Haskell.)


If you are willing to encode your types as generalized tuples, i.e. 
heterogeneous lists, you can do that:


import Data.Monoid

data Nil = Nil
data Cons a bs = Cons a bs
-- type Socket 3 a b c = Cons a (Cons b (Cons c Nil))
-- (feel free to use operator syntax to prettify it)

instance Monoid Nil where
  mempty = Nil
  mappend Nil Nil = Nil

instance (Monoid a, Monoid bs) = Monoid (Cons a bs) where
  mempty = Cons mempty mempty
  mappend (Cons x1 ys1) (Cons x2 ys2) = Cons (mappend x1 x2) (mappend 
ys1 ys2)



-- Steffen

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


[Haskell-cafe] ANNOUNCE: apphointments - A simple functional calendar

2012-10-18 Thread Steffen Schuldenzucker


Dear Café,

I just wrote myself a small (~ 200 LOC) calendar application today.

https://bitbucket.org/rainmaker/apphointments

Comments/Patches welcome.

From the readme:

apphointments - A simple functional calendar


This is a UI = Code calendar application: You create an event by writing
code that defines it.
To see what's up next, you create a report, i.e. a summary of the 
events in

a certain time range such as 'thisWeek'. This is done by haskell functions
again from GHCi or ghc -e.

See example.hs.

Using just haskell instead of our own language or GUI allows great 
flexibility

in both defining events and generating reports. See e.g. the 'lecture'
combinator from Apphointments.Util.

Status
--

Works for me, but has no features yet.
See TODO.

Credits
---

Created by Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de


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


Re: [Haskell-cafe] How to define a Monad instance

2012-07-28 Thread Steffen Schuldenzucker

On 07/28/2012 03:35 PM, Thiago Negri wrote:
 [...]

As Monads are used for sequencing, first thing I did was to define the
following data type:

data TableDefinition a = Match a a (TableDefinition a) | Restart


So TableDefinition a is like [(a, a)].


[...]



So, to create a replacement table:

table' :: TableDefinition Char
table' =
 Match 'a' 'b'
 (Match 'A' 'B'
  Restart)

It look like a Monad (for me), as I can sequence any number of
replacement values:

table'' :: TableDefinition Char
table'' = Match 'a' 'c'
  (Match 'c' 'a'
  (Match 'b' 'e'
  (Match 'e' 'b'
   Restart)))


Yes, but monads aren't just about sequencing. I like to see a monad as a 
generalized computation (e.g. nondeterministic, involving IO, involving 
state etc). Therefore, you should ask yourself if TableDefinition can be 
seen as some kind of abstract computation. In particular, can you 
execute a computation and extract its result? as in


  do
r - Match 'a' 'c' Restart
if r == 'y' then Restart else Match 2 3 (Match 3 4 Restart)

Doesn't immediately make sense to me. In particular think about the 
different possible result types of a TableDefinition computation.


If all you want is sequencing, you might be looking for a Monoid 
instance instead, corresponding to the Monoid instance of [b], where 
b=(a,a) here.



 [...]



I'd like to define the same data structure as:

newTable :: TableDefinition Char
newTable = do
 'a' :  'b'
 'A' :  'B'

But I can't figure a way to define a Monad instance for that. :(


The desugaring of the example looks like this:

  ('a' : 'b')  ('A' : 'B')

Only () is used, but not (=) (i.e. results are always discarded). If 
this is the only case that makes sense, you're probably looking for a 
Monoid instead (see above)


-- Steffen

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


Re: [Haskell-cafe] Finding the average in constant space

2012-05-27 Thread Steffen Schuldenzucker


Hi Chris,

On 05/27/2012 10:04 AM, Chris Wong wrote:

I just came up with a way of executing multiple folds in a single
pass. In short, we can write code like this:

average = foldLeft $ (/)$  sumF*  lengthF

and it will only traverse the input list once.

The code is at: https://gist.github.com/2802644

My question is: has anyone done this already? If not, I might release
this on Hackage -- it seems quite useful.


This is (a special case of) the main point in the design of iteratees. 
See e.g. the definition of the 'Iteratee' type in the enumeratee 
library. - Looks pretty much like your 'Fold' type with an additional 
state (done or not yet done).


Also, the pipe package seems to provide something similar.

-- Steffen

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: notcpp-0.0.1

2012-04-15 Thread Steffen Schuldenzucker



On 04/13/2012 10:49 PM, Ben Millwood wrote:

I'm pleased to announce my first genuinely original Hackage package:
notcpp-0.0.1!

http://hackage.haskell.org/package/notcpp

[...]


Why is it

 scopeLookup :: String - Q Exp
with n bound to x :: T = @scopeLookup n@ evaluates to an Exp containing 
@Just x@


, not

 scopeLookup :: String - Q (Maybe Exp)
with n bound to x :: T = @scopeLookup n@ evaluates to Just (an Exp 
containing @x@)


? Shouldn't n's being in scope be a compile time decision? That would 
also make the openState: runtime name resolution has its drawbacks 
:/[1] a compile time error.


-- Steffen

[1] 
http://hackage.haskell.org/packages/archive/notcpp/0.0.1/doc/html/NotCPP-ScopeLookup.html


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


Re: [Haskell-cafe] Understanding GC time

2012-03-12 Thread Steffen Schuldenzucker



On 03/10/2012 07:50 PM, Thiago Negri wrote:

I see. Thanks for the answers.

Any data structure or source annotation that would prevent that?

For example, if I try the same program to run on a
[1..] list, I'll get an out of memory error for the
single-threaded version. Any way to prevent it without declaring two
different versions of list?



Maybe you'd like to treat your list more like a stream of input data, 
similar to, say, user input via IO? If your algorithms generalize to 
such streams, you can be sure that they don't force the whole list into 
memory (at least not accidentally).


You might want to take a look at iteratees or conduits.

-- Steffen



2012/3/10 Anthony Cowleyacow...@gmail.com:

 From that profiling data, I think you're just seeing a decrease in sharing. 
With one thread, you create the list structure in memory: the first fold could 
consume it in-place, but the second fold is still waiting for its turn.  The 
list is built on the heap so the two folds can both refer to the same list.

With two threads, GHC is being clever and inlining the definition you give for 
list, which is then optimized into two parallel loops. No list on the heap 
means there's not much for the GC to do.

Sharing of index lists like this is a common source of problems. In particular, 
nested loops can make it even trickier to prevent sharing as there may not be 
an opportunity for parallel evaluation.

Anthony

On Mar 10, 2012, at 10:21 AM, Thiago Negrievoh...@gmail.com  wrote:


Hi all.

I wrote a very simple program to try out parallel Haskel and check how
it would look like to make use of more than one core in this language.

When I tried the program with RTS option -N1, total time shows it took
2.48 seconds to complete and around 65% of that time was taken by GC.

Then I tried the same program with RTS options -N2 and total time
decreased to 1.15 seconds as I expected a gain here. But what I didn't
expect is the GC time to drop to 0%.

I guess I'm having trouble to understand the output of the RTS option -s.
Can you enlighten me?


The source for the testing program:


module Main where

import Data.List (foldl1')
import Control.Parallel (par, pseq)
import Control.Arrow (())

f `parApp` (a, b) = a `par` (b `pseq` (f a b))
seqApp = uncurry

main = print result
  where result = (+) `parApp` minMax list
minMax = minlist  maxlist
minlist = foldl1' min
maxlist = foldl1' max
list = [1..1999]



The results on a Windows 7 64bits with an Intel Core 2 Duo, compiled
with GHC from Haskell Platform:

c:\tmp\hspar +RTS -s -N1
par +RTS -s -N1
2000
 803,186,152 bytes allocated in the heap
 859,916,960 bytes copied during GC
 233,465,740 bytes maximum residency (10 sample(s))
  30,065,860 bytes maximum slop
 483 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1523 collections, 0 parallel,  0.80s,  0.75s elapsed
  Generation 1:10 collections, 0 parallel,  0.83s,  0.99s elapsed

  Parallel GC work balance: nan (0 / 0, ideal 1)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :0.00s(  0.90s)   0.00s(  0.06s)
  Task  1 (worker) :0.00s(  0.90s)   0.00s(  0.00s)
  Task  2 (bound)  :0.86s(  0.90s)   1.62s(  1.69s)

  SPARKS: 1 (0 converted, 0 pruned)

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.86s  (  0.90s elapsed)
  GCtime1.62s  (  1.74s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time2.48s  (  2.65s elapsed)

  %GC time  65.4%  (65.9% elapsed)

  Alloc rate936,110,032 bytes per MUT second

  Productivity  34.6% of total user, 32.4% of total elapsed

gc_alloc_block_sync: 0
whitehole_spin: 0
gen[0].sync_large_objects: 0
gen[1].sync_large_objects: 0


c:\tmp\hspar +RTS -s -N2
par +RTS -s -N2
2000
   1,606,279,644 bytes allocated in the heap
  74,924 bytes copied during GC
  28,340 bytes maximum residency (1 sample(s))
  29,004 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1566 collections,  1565 parallel,  0.00s,  0.01s elapsed
  Generation 1: 1 collections, 1 parallel,  0.00s,  0.00s elapsed

  Parallel GC work balance: 1.78 (15495 / 8703, ideal 2)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :0.00s(  0.59s)   0.00s(  0.00s)
  Task  1 (worker) :0.58s(  0.59s)   0.00s(  0.01s)
  Task  2 (bound)  :0.58s(  0.59s)   0.00s(  0.00s)
  Task  3 (worker) :0.00s(  0.59s)   0.00s(  0.00s)

  SPARKS: 1 (1 converted, 0 pruned)

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time1.15s  (  0.59s elapsed)
  GCtime0.00s  (  0.01s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time1.15s  (  0.61s elapsed)

  %GC time   0.0%  (2.4% elapsed)

  Alloc

Re: [Haskell-cafe] STM atomic blocks in IO functions

2012-01-14 Thread Steffen Schuldenzucker

On 01/14/2012 03:55 PM, Ketil Malde wrote:

Bryan O'Sullivanb...@serpentine.com  writes:


The question is a simple one. Must all operations on a TVar happen
within *the same* atomically block, or am I am I guaranteed thread
safety if, say, I have a number of atomically blocks in an IO
function.



If you want successive operations to see a consistent state, they must
occur in the same atomically block.


I'm not sure I understand the question, nor the answer?  I thought the
idea was that state should be consistent on the entry and exit of each
atomically block.  So you can break your program into multiple
transactions, but each transaction should be a semantically complete
unit.


I think consistent state here means that you can be sure no other 
thread has modified a, say, TVar, within the current 'atomically' block.


E.g. for MVars, you could /not/ be sure that

  void (takeMVar mvar)  putMVar mvar 5

won't block if mvar is full at the beginning, because a different thread 
might put to mvar between the two actions. However, in


  atomically $ void (takeTVar tvar)  putTVar tvar 5

, this is not possible, the action after 'atomically' won't be 
influenced by any other threads while it's running, hence the name.


-- Steffen

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


Re: [Haskell-cafe] named pipe interface

2012-01-12 Thread Steffen Schuldenzucker


On 01/12/2012 07:53 PM, Serge D. Mechveliani wrote:

[...]



For the to-A part writen in C  (instead of Haskell), this interface
loop works all right.
With Haskell, I manage to process only a single string in the loop,
and then it ends with an error.

Main.hs  is given below.

I never dealt with such an IO in Haskell.
Can you, please, fix the code or give comments?

Please, copy the response to  mech...@botik.ru
(I am not in the list).

[...]
---
import System.IO (IOMode(..), IO(..), Handle, openFile, hPutStr,
   hGetLine, hFlush)
import System.IO.Unsafe (unsafePerformIO)

dir = showString /home/mechvel/ghc/axiomInterface/byLowerLevel/

toA_IO   = openFile (dir toA)   WriteMode:: IO Handle
fromA_IO = openFile (dir fromA) ReadMode
-- used as global values
toA   = unsafePerformIO toA_IO --
fromA = unsafePerformIO fromA_IO   --

axiomIO :: String -  IO String
axiomIO str = do
   hPutStr toA str
   hFlush toA
   hGetLine fromA

axiom :: String -  String -  String
axiom str =  showString (unsafePerformIO $ axiomIO str)

-- Examples of usage 


tl;dr, but did you try to write your program without using 
unsafePerformIO? It's considered harmful for a reason.


Cheers, Steffen

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


Re: [Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-06 Thread Steffen Schuldenzucker



On 01/06/2012 11:16 AM, Steve Horne wrote:


I was messing around with type-classes (familiarization exercises) when
I hit a probably newbie problem. Reducing it to the simplest case...

module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where
-- n : node type
-- d : data item type wrapped in each node
class WalkableBinTree n where
wbtChildren :: n - Maybe (n, n)
wbtData :: n - Maybe d


With 'd' not being mentioned anywhere, the signature of wbtData means 
forall d. n - Maybe d. In particular, wbtData == const Nothing.




-- Simple tree type, mostly for testing
data BT x = Branch x (BT x) (BT x)
| Empty

instance WalkableBinTree (BT x) where
wbtChildren (Branch d l r) = Just (l, r)
wbtChildren Empty = Nothing

wbtData (Branch d l r) = Just d
wbtData Empty = Nothing


The signature of this function is 'BT x - Maybe x', so it doesn't match 
the one above.




Loading this code into GHCi, I get...

Prelude :load BinTree
[1 of 1] Compiling BinTree ( BinTree.hs, interpreted )

BinTree.hs:16:39:
Couldn't match type `x' with `d'
`x' is a rigid type variable bound by
the instance declaration at BinTree.hs:12:32
`d' is a rigid type variable bound by
the type signature for wbtData :: BT x - Maybe d
at BinTree.hs:16:5
In the first argument of `Just', namely `d'
In the expression: Just d
In an equation for `wbtData': wbtData (Branch d l r) = Just d
Failed, modules loaded: none.
Prelude


...which this error message tells you.



I've tried varying a number of details. Adding another parameter to the
type-class (for the item-data type) requires an extension, and even then
the instance is rejected because (I think) the tree-node and item-data
types aren't independent.


Did you try something like

 {-# LANGUAGE MultiParamTypeClasses #-}
 class WalkableBinTree n d where
   ... (same code as above, but 'd' is bound now)
 ...
 instance WalkableBinTree (BT x) x where
   ...

-- Steffen

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


Re: [Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-06 Thread Steffen Schuldenzucker



On 01/06/2012 11:51 AM, Steve Horne wrote:

On 06/01/2012 10:29, Steffen Schuldenzucker wrote:

On 01/06/2012 11:16 AM, Steve Horne wrote:

 [...]


module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where
-- n : node type
-- d : data item type wrapped in each node
class WalkableBinTree n where
wbtChildren :: n - Maybe (n, n)
wbtData :: n - Maybe d


[...]

Did you try something like

 {-# LANGUAGE MultiParamTypeClasses #-}
 class WalkableBinTree n d where
 ... (same code as above, but 'd' is bound now)
 ...
 instance WalkableBinTree (BT x) x where
 ...



 [...]


If I specify both extensions (-XMultiParamTypeClasses and
-XFlexibleInstances) it seems to work, but needing two language
extensions is a pretty strong hint that I'm doing it the wrong way.

 [...]

Well, if your instances always look like

 instance WalkableBinTree (SomeTypeConstructor x) x

you could make WalkableBinTree take a type constructor of kind (* - *) 
like this:


 class WalkableBinTree t where
 wbtChildren :: t x - (t x, t x)
 wbtData :: t x - Maybe x
 instance WalkableBinTree BT where ...

Of course, you loose flexibility compared to the multi param approach, 
e.g. you couldn't add type class constraints for the element type 'x' in 
an instance declaration.


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


Re: [Haskell-cafe] Anonymous, Unique Types, maybe

2011-12-04 Thread Steffen Schuldenzucker


On 12/04/2011 06:53 AM, Scott Lawrence wrote:

[...]
Some operators might take more than one list/stream as an argument,
combining them in some way or another. Obviously, if the lists were
different lengths, the operator would fail. I don't want that to happen
at run time, so I want to check for it statically, presumably via the
type system. I could do this manually:

type AList = [Event]
type BList = [Event]
type CList = [Event]

myMapish :: AList - AList
mySelect :: AList - (Event - Bool) - BList
myOtherSelect :: BList - CList

 [...]

Just as a small side note, with the 'type' keyword, AList, BList, CList 
will /not/ be seen as separate types (but they're all the same type, 
namely [Event]).

If you want separate types, you would use a newtype wrapper like

newtype AList = AList [Event]
deriving (some instances you want to derive from [Event])

-- Steffen

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


Re: [Haskell-cafe] Anonymous, Unique Types, maybe

2011-12-04 Thread Steffen Schuldenzucker


Hi Scott,

a good idea. Why not use an existential to encode your types like

myMap :: (a - b) - a-list of length n
- b-list of length n
myFilter :: (a - Bool) - a-list of length n
- exists m. a-list of length m

, where the first case is modeled using a type annotation and the second 
using an existential:



 {-# LANGUAGE ExistentialQuantification #-}

 -- just for @data S@ at the very end.
 {-# LANGUAGE EmptyDataDecls #-}

 -- don't export the LList constructor!
 data LList n a = LList [a]

 llist2List :: LList n a - [a]
 llist2List (LList xs) = xs

 unsafeList2LList :: [a] - LList n a
 unsafeList2LList = LList

 unsafeWrapLList :: ([a] - [b]) - LList n a - LList m b
 unsafeWrapLList f = unsafeList2LList . f . llist2List

 unsafeCoerceLList :: LList n a - LList m a
 unsafeCoerceLList = unsafeWrapLList id

 mapLList :: (a - b) - LList n a - LList n b
 mapLList f = unsafeList2LList . map f . llist2List


 -- should be exported.
 data SomeLList a = forall n. SomeLList (LList n a)

 -- this is safe again! (SomeLList a) is a lot like [a].
 list2SomeLList :: [a] - SomeLList a
 list2SomeLList = SomeLList . unsafeList2LList

 wrapSomeLList :: ([a] - [b]) - SomeLList a - SomeLList b
 wrapSomeLList f (SomeLList ll) = list2SomeLList . f . llist2List $ ll

 myFilter :: (a - Bool) - LList n a - SomeLList a
 myFilter p = list2SomeLList . filter p . llist2List

 -- NOTE that we're being extremely imprecise about the length of
 -- lists. We don't say one less, but just potentially different.
 myTail :: LList n a - SomeLList a
 myTail lst = case llist2List lst of
 [] - error myTail: empty list
 (_:xs) - list2SomeLList xs

 myMap :: (a - b) - LList n a - LList n b
 myMap = mapLList

 myMatchingZip :: LList n a - LList n b - LList n (a, b)
 myMatchingZip xs ys = unsafeList2LList $
 zip (llist2List xs) (llist2List ys)

 -- test:

 test_input :: (Num a, Enum a) = [a]
 test_input = [1..10]

 test_works :: (Num a, Enum a) = SomeLList (a, a)
 test_works = SomeLList $ case list2SomeLList test_input of
 (SomeLList il) - myMatchingZip il (myMap (*2) il)
 -- ^ It's important to have the input bound to /one/ variable
 -- of type LList n a ('il' here).
 -- Otherwise, we don't get enough type equality.

 {-
 -- @myMatchingZip il (myFilter isEven il)@ plus type safety.
 -- Gives a Couldn't match type `n1' with `n' type error, which is 
correct.

 test_illegal = SomeLList $ case list2SomeLList test_input of
 (SomeLList il)- case myFilter isEven il of
   (SomeLList evens) - myMatchingZip il evens
 where isEven x = x `mod` 2 == 0
 -}


So 'n' here corresponds to what your 'a' is below, and 'a' here is 
always 'Event' below.


Note that you don't have to actually encode the length of lists in the 
type system using this approach. I hit a similar problem some months ago 
when trying to model financial contracts:
Prices are only comparable when they are given at the same time and in 
the same currency, but I wasn't going to encode currencies or times in 
the type system. I just wanted the compiler to check if it could prove 
two prices are compatible and if not, I would convert them (which was 
cheap).


Using more sophisticated types for 'n', we can express richer 
properties. For example:


 data S n

 myBetterTail :: LList (S n) a - LList n a
 myBetterTail l = case myTail l of
 (SomeLList ll) - unsafeCoerceLList ll

 myBetterCons :: a - LList n a - LList (S n) a
 myBetterCons x = unsafeWrapLList (x:)

 test_do_nothing :: a - LList n a - LList n a
 test_do_nothing x = myBetterTail . myBetterCons x

Cheers, Steffen

On 12/04/2011 06:53 AM, Scott Lawrence wrote:

(Sorry if this email is rather unclear - I know my desired end result,
but neither how to acheive nor explain it well. Here goes.)

I'm processing lists, using them sortof as streams. (Whether that's a
good idea isn't the issue here - but let me know if it isn't!)
Fundamentally, there are two types of operations (at least, that are
relevant here) - those that change the length of the list and those that
don't.

Some operators might take more than one list/stream as an argument,
combining them in some way or another. Obviously, if the lists were
different lengths, the operator would fail. I don't want that to happen
at run time, so I want to check for it statically, presumably via the
type system. I could do this manually:

type AList = [Event]
type BList = [Event]
type CList = [Event]

myMapish :: AList - AList
mySelect :: AList - (Event - Bool) - BList
myOtherSelect :: BList - CList

but I'd rather not have to manually define a new type for every new list
length:

myMapish :: List a - List a
mySelect :: List a - List ?

The '?' would be an anonymous, unique type - unless there's a better way
to accomplish this.

Hope that was clear, and thanks (as always) for the help (and being
awesome).



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

Re: [Haskell-cafe] Fwd: Is it possible to represent such polymorphism?

2011-10-06 Thread Steffen Schuldenzucker

On 10/05/2011 11:30 PM, Alberto G. Corona wrote:


if Hlist is sugarized as variable length tuples, then the initial code
would compile without noticing the use of HList...


Seems to me like the advantage of such a sugaring would be that people 
could use a complex framework without actually having to think about it. 
On the other hand, the greatest disadvantage would be that people could 
use a complex framework without actually having to think about it.





2011/10/5 Felipe Almeida Lessa felipe.le...@gmail.com
mailto:felipe.le...@gmail.com

On Wed, Oct 5, 2011 at 8:45 AM, Alberto G. Corona
agocor...@gmail.com mailto:agocor...@gmail.com wrote:
  If a newbie considers this as something natural, this is another
reason for
  syntactic sugaring of HList:
  http://www.haskell.org/pipermail/haskell-cafe/2011-April/090986.html

Exposing newbies to HList seems like a recipe for disaster for me =).

--
Felipe.





___
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] Problem on using class as type.

2011-10-03 Thread Steffen Schuldenzucker

On 10/03/2011 10:42 PM, Magicloud Magiclouds wrote:

Hi,
   I have a function:
post :: (ToJson p, FromJson q) =  String -  String -  String -
Map.Map String p -  IO q
   Now I'd like to call it like:
r- post site token user.addMedia (Map.fromList [ (users, users :: ToJson)
, (medias, medias
:: ToJson) ])
   So I got the problem. If I used things like users :: ToJson, then
class used as a type error occurred. But if I did not use them, since
users and medias were actually different types, then fromList failed,
required the type of medias the same with users.

   How to resolve the conflict?


If 'users' and 'medias' are actually of a general type (like for all a 
with ToJson a, users describes a value of type a), use Jesse's 
suggestion. Otherwise (there is an a with ToJson a such that users 
describes a value of type a), you might want to use existentials:


{-# LANGUAGE ExistentialQuantification #-}
data SomeToJson = forall a. (ToJson a) = SomeToJson a

instance ToJson SomeToJson where
toJson (SomeToJson x) = toJson x  -- I guess your class looks like 
this?


And then:
r - post site token user.addMedia $ Map.fromList
[(users, SomeToJson users), (medias, SomeToJson medias)]

As a last remark, I needed this pattern exactly once, namely for dealing 
with rank 2 types in rendering functions using takusen. I can conclude 
that requiring it is often an indicator for a major design flaw in your 
program. In this case:


Why not:

-- assuming that there is an
-- instance ToJson Json where toJson = id
r - post site token user.addMedia $ Map.fromList
   [(users, toJson users), (medias, toJson medias)]

Cheers!

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


Re: [Haskell-cafe] Improvements to Vim Haskell Syntax file - Is anyone the maintainer?

2011-09-08 Thread steffen
Hi,

check out this one:
https://github.com/urso/dotrc/blob/master/vim/syntax/haskell.vim

A (not up to date) version of it can also be found on vim.org:
http://www.vim.org/scripts/script.php?script_id=3034

It is not an official version, but already a modification of the original 
syntax file, plus some new features.

Unfortunately I haven't had time to maintain and update the syntax file for 
a (lng) while, but hopefully next week I will have some time to do 
some maintenance. I plan to incorporate out standing pull requests, do some 
improvements and split of the script itself into a new project on github 
with test cases, readme and screen shots.

If you've done any changes which may benefit the syntax file I would be glad 
about patches or pull requests on github.

I'm using github at the moment, but am open for suggestions about other 
hosting ideas (e.g. bitbucket plus github mirror or hackage). As I've made 
some extensive changes I will continue maintaining the syntax file (unless 
someone else really wants to do it...), but I'd prefer it to be a 
haskell-comunity project so other people can join in easily and propose 
changes.

- Steffen

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


[Haskell-cafe] Fwd: Re: How to select last inserted record from Table Using Database.HSQL.MySQL

2011-07-26 Thread Steffen Schuldenzucker

Forwarding to list

 Original Message 
Subject:Re: [Haskell-cafe] How to select last inserted record from
Table Using Database.HSQL.MySQL
Date:   Tue, 26 Jul 2011 14:27:56 +0300
From:   Sergiy Nazarenko nazarenko.ser...@gmail.com
To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de



Thanx a lot!

I could solve that problem in this way:

cmd =  INSERT INTO mytable (bar,foo) VALUES (val1,val2); SELECT
LAST_INSERT_ID() as id;
lst - query connection cmd = collectRows (\st - getFieldValue st id)

lst has required value

Cheers!


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


Re: [Haskell-cafe] How to select last inserted record from Table Using Database.HSQL.MySQL

2011-07-25 Thread Steffen Schuldenzucker


Hello Sergiy,

On 07/25/2011 04:54 PM, Sergiy Nazarenko wrote:

Hi, everyone!

trycon - connect mysql bigtables vasya ***
stmt' - query trycon INSERT INTO mytable (user,time,host,) VALUES
(Vasya,2011.07.30 11.59,foo)

I am beginner to use HSQL and I have a problem.
I need to know row ID after INSERT into table.

fetch stmt'  returned False

What should I do?


This does not seem to be HSQL specific. For mysql, Google gave me 
LAST_INSERT_ID():


http://dev.mysql.com/doc/refman/5.0/en/information-functions.html#function_last-insert-id

There probably exist similar functions for other sql databases.

-- Steffen

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


Re: [Haskell-cafe] pointer equality

2011-07-21 Thread Steffen Schuldenzucker


On 07/21/2011 10:30 AM, Pedro Vasconcelos wrote:

On Wed, 20 Jul 2011 12:48:48 -0300
Thiago Negrievoh...@gmail.com  wrote:



Is it possible to implement (==) that first check these thunks before
evaluating it? (Considering both arguments has pure types).


E.g.,

Equivalent thunks, evaluates to True, does not need to evaluate its
arguments: [1..] == [1..]




Thunks are just expressions and equality of expressions is undecidable
in any Turing-complete language (like any general-purpose programming
language). Note that syntactical equality is not sufficient because
(==) should be referentially transparent.


I think the following code pretty much models what Thiago meant for a 
small subset of haskell that constructs possibly infinite lists. Thunks 
are made explicit as syntax trees. 'Cycle' is the syntactic symbol for a 
function whose definition is given by the respective case in the 
definition of 'evalOne'.
(I chose cycle here instead of the evalFrom example above to because it 
doesn't need an Enum constraint).


The interesting part is the definition of 'smartEq'.

import Data.List (unfoldr)
import Data.Function (on)

-- let's say we have syntactic primitives like this
data ListExp a = Nil | Cons a (ListExp a) | Cycle (ListExp a)
deriving (Eq, Ord, Read, Show)
-- derives syntactic equality

conss :: [a] - ListExp a - ListExp a
conss xs exp = foldr Cons exp xs

fromList :: [a] - ListExp a
fromList xs = conss xs Nil

-- eval the next element, return an expression defining the tail
-- (if non-empty)
evalOne :: ListExp a - Maybe (a, ListExp a)
evalOne Nil = Nothing
evalOne (Cons h t) = Just (h, t)
evalOne e@(Cycle exp) = case eval exp of
[] - Nothing
(x:xs) - Just (x, conss xs e)

eval :: ListExp a - [a]
eval = unfoldr evalOne

-- semantic equality
evalEq :: (Eq a) = ListExp a - ListExp a - Bool
evalEq = (==) `on` eval

-- semantic equality, but check syntactic equality first.
-- In every next recursion step, assume the arguments of the current 
recursion

-- step to be equal. We can do that safely because two lists are equal iff
-- they cannot be proven different.
smartEq :: (Eq a) = ListExp a - ListExp a - Bool
smartEq a b = smartEq' a b []

smartEq' :: (Eq a) = ListExp a - ListExp a - [(ListExp a, ListExp a)] 
- Bool

smartEq' a b eqPairs = if a == b || (a, b) `elem` eqPairs
then True
else case (evalOne a, evalOne b) of
(Just _, Nothing)  - False
(Nothing, Just _)  - False
(Nothing, Nothing) - True
(Just (h1, t1), Just (h2, t2)) - h1 == h2  smartEq' t1 t2 ((a, 
b):eqPairs)


Examples:

*Main smartEq (Cycle $ fromList [1]) (Cycle $ fromList [1,1])
True
*Main smartEq (Cons 1 $ Cycle $ fromList [1]) (Cycle $ fromList [1])
True
*Main smartEq (Cons 2 $ Cycle $ fromList [1]) (Cycle $ fromList [1])
False

Any examples for hangups of 'smartEq' are greatly appreciated, I 
couldn't produce any so far.


-- Steffen


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


Re: [Haskell-cafe] pointer equality

2011-07-21 Thread Steffen Schuldenzucker

On 07/21/2011 02:15 PM, Alexey Khudyakov wrote:

Any examples for hangups of 'smartEq' are greatly appreciated, I couldn't
produce any so far.


Following sequences will hang smartEq. They are both infinite and aperiodic.
  smartEq (fromList primes) (fromList primes)
  smartEq (fromList pidigits) (fromList pidigits)


Err, yeah, of course. I would expect expressions of type ListExp to be 
finite as they represent written text.

fromList therefore expects to receive only finite lists.

Defining 'primes' using my method seems to be a bit of a challenge due 
to its recursive definition.


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


Re: [Haskell-cafe] Make Show instance

2011-07-21 Thread Steffen Schuldenzucker


Hi.

On 07/21/2011 04:45 PM, Александр wrote:

Hello,

I have binary tree, with every leaf tuple - (k,v):

data Tree k v = EmptyTree
| Node (k, v) (Tree k v) (Tree k v)

How can i make Show Instance for (Tree Int Int) ?


The easiest way is automatic derivation:

data Tree k v = EmptyTree
  | Node (k, v) (Tree k v) (Tree k v)
  deriving (Eq, Ord, Show, Read)
  -- you normally want at least these four.

Then the compiler automatically declares the instances for you, given 
that 'k' and 'v' have them. For k = v = Int, this is the case.




I try:

instance Show (Tree k v) where
show EmptyTree = show Empty
show (Node (Int, Int) left right) = ..


I'm afraid to say that, but 'Int' doesn't make sense at this place. You 
would want


 show (Node (x, y) left right) = ...

instead. (That is, use any variables. Variables have to be lowercase.)

-- Steffen

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


Re: [Haskell-cafe] Type checking oddity -- maybe my own confusion

2011-07-12 Thread Steffen Schuldenzucker

On 07/12/2011 05:01 PM, Ryan Newton wrote:

Hi all,

Is there something wrong with the code below?  My anticipation was that
the type of test would include the class constraint, because it uses
the Assign constructor.  But if you load this code in GHCI you can see
that the inferred type was test :: E m - E m.


When I complete the pattern match in 'test', it might look like this:

test x = case x of
Assign v e1 e2 - x
Varref v - x

(which is just id :: E m - E m). Of course, we want to be able to write

 test (Varref v)

for any v :: V, and match the second case. But as 'Varref' does not add 
an AssignCap constraint, 'test' must not either.


Hope that helps. Steffen



Thanks,
   -Ryan


{-# LANGUAGE GADTs #-}

class AssignCap m
data PureT
data IOT
instance AssignCap IOT

data E m where
   Assign  :: AssignCap m = V - E m - E m - E m
   Varref  :: V - E m
-- ...

type V = String

-- I expected the following type but am not getting it:
-- test :: AssignCap m = E m - E m
test x =
   case x of
Assign v e1 e2 - Assign v e1 e2
-- And this is the same:
Assign v e1 e2 - x



___
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] class and instance

2011-07-10 Thread Steffen Schuldenzucker

On 07/10/2011 12:49 PM, Patrick Browne wrote:

Hi,
I am trying to understand the following code.
I have written my current (mis-)understanding and questions below.
I do not wish to improve the code, it is from a research paper[1] that I
am trying to understand.

Pat
[1] ftp://ftp.geoinfo.tuwien.ac.at/medak/phdmedak.pdf

-- A specification. The class Points takes two type variables.
-- The functions take variables of type p, a; return a value of type a.


No. The class 'Points' takes two type variables, 'p' of kind (* - *) 
(that is, p is a type constructor: it can be applied to a type, yielding 
a type), and 'a' of kind *.
Then 'p a' is a type and getX, getY take /one/ argument respectively, of 
this type.



  class Points p a where
   getX :: p a -  a
   getY :: p a -  a

-- A parameterized representation
-- One constructor takes two elements of type a and produces a Point.
  data Point a = Pt a a

-- An implementation of the class Points on the data type (Point a)


Actually, it's an implementation (we say instance) of the class Points 
for the type constructor 'Point' and any type 'a'.



-- In  Pt b c constructor the variables b and c areboth of type a.
-- The type a is left undefined until evaluation


I would say 'arbitrary' instead of 'undefined': The code below says that 
for any type of your choice, which we call 'a', you get an instance 
Points Point a.



  instance Points Point a where
   getX (Pt b c) = b
   getY (Pt b c) = c

-- This runs with any type e.g. Integers
-- getX(Pt 1 2)
-- :t getX(Pt 1 2)
-- getX(Pt 1 2) :: forall t. (Num t) =  t


My main question is in understanding the relationship between the
arguments of the functions getX and getY in the class and in the
instance. It seems to me that the constructor Pt 1 2 produces one
element of type Point which has two components. How does this square
with the class definition of getX which has two arguments?
Is there a difference between:
getX :: p a -  a
  and
getX :: p -  a -  a


Yes, the first version takes one argument of type 'p a', and the second 
takes two of types 'p' and 'a'. See above. This seemed to be you main issue.


As a last note, if you always have instances like the one above, where 
the second parameter is arbitrary, your definition of the class 'Points' 
could be simplified to


 class Points p where
   -- forall a is added implicitly.
   getX :: p a - a
   getY :: p a - a

 instance Points Point where
   -- copy'n'paste from above

-- Steffen

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


Re: [Haskell-cafe] Arrow instance of function type [a] - [b]

2011-07-06 Thread Steffen Schuldenzucker


Hi Markus,

On 07/06/2011 03:04 PM, Markus Läll wrote:

[...]

import Control.Arrow
import Control.Category

type X a b = [a] -  [b]

instance Category X where
id = map Prelude.id
g . f = g Prelude.. f

instance Arrow X where
arr f = map f
first f = unzip  first f  uncurry zip

The problem is that it's not allowed to use partially applied type
synonyms. It is however possible to define a type synonym which value
is a partially applied type, but I haven't been able to figure out if
I could somehow use that fact in defining the X... Is it at all
possible, or is a newtype the only way to do it?



You should really use a newtype for that. Allowing partially applied 
type synonyms would greatly increase the expressiveness of the type 
language. (too much, actually)

In fact, you could write arbitrary type level lambdas, like that:

 type Y b a = [a] - [b]

But now, given instances like this:

 instance Category X where ...

 instance Category Y where ...
 -- uh, yeah, does it make sense in this case? Whatever, we *could* 
have an instance.


, any function of type [a] - [b] will match both instances. So which 
instance to choose? We have two solutions:


a) The compiler discovers itself that we have overlaps here and complains.

This seems hard to me (is it even possible in finite time?). Note that 
it is easy if type synonyms are always fully applied because the 
compiler just has to fill in the definition of all the types and can 
then proceed to compare just the instance *heads*.


b) You somehow annotate which instance to choose for each specific case. 
But that's exactly what newtypes are for!


The problem does indeed occur in your example: What is (id :: [a] - 
[b]) supposed to be, Prelude.id (as given by the general instance for 
functions) or map Prelude.id (given by your instance)?


-- Steffen

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


Re: [Haskell-cafe] Automatic Reference Counting

2011-07-05 Thread steffen
The important point about reference counting on idevices is the near 
realtime performance, since stops for collecting garbage are actually very 
short in comparison to collecting compilers (despite more frequent). Some 
compilers, I think it was for the pure functional programming language OPAL 
if I'm not wrong even check at compile time and add code for reusing cells 
instead of freeing them when it is known to be safe. But OPAL has strict 
evaluation and no lazy construct. This it does not allow for cycles unlike 
haskell which makes reference counting a viable and easy implementable 
option for OPAL.

About Apple's ARC. It is actually using the very same mechanisms the clang 
static analyzer uses. That is at a first stage it works with the typical 
Objective-C conventions of object ownership. For example if you have a 
function other than alloc and Co. transferring object ownership to it's 
caller the static analyzer will complain about a possible space leak. In 
this case one has to add an attribute to the function telling the compiler 
that it is intended for the function to work like this. Having a look at the 
ARC docs it seems to be the very same case. That is if you have a function 
like just mentioned you need to add this said attribute to the function 
declaration for ARC to insert correct retains/releases. 

So there is no real magic going on, but one needs to be really aware of it 
or bug hunting (especially for external libraries) may become maybe a 
little less funny...

Additionally clang adds some extra commands into the generated LLVM code 
which LLVM understands. This allows i) for further optimizations at later 
compiling stages and ii) you don't need to send messages to objects anymore 
for reference counting (as long as you don't implement retain/release for 
them by yourself, but by convention you don't do so...), but the counter may 
be accessed directly in memory. That's why ARC (if you follow Apple's 
conventions about object ownership) can be much more efficient than the 
current implementation.

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


Re: [Haskell-cafe] overloading show function

2011-06-29 Thread Steffen Schuldenzucker


Hi Philipp,

On 06/29/2011 11:50 PM, Philipp Schneider wrote:

Hi cafe,

in my program i use a monad of the following type

newtype M a = M (State -  (a, State))


btw., it looks like you just rebuilt the State monad.



...

instance (Show a,Show b) =  Show (M (a,b)) where
show (M f) = let ((v,_), s) = f 0 in
  Value:  ++ show v ++   Count:  ++ show s

instance Show a =  Show (M a) where
show (M f) = let (v, s) = f 0 in
  Value:  ++ show v ++   Count:  ++ show s

however this gives me the following error message:

 Overlapping instances for Show (M (Value, Environment))
   arising from a use of `print'
 Matching instances:
   instance (Show a, Show b) =  Show (M (a, b))
 -- Defined at
/home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
   instance Show a =  Show (M a)
 -- Defined at
/home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
 In a stmt of an interactive GHCi command: print it


This is a well-known issue. The problem is as follows: Your second 
instance declares an instance Show (M a) for any type a. If a is of the 
Form (b, c), we can derive a tuple instance from that. This however 
conflicts with the tuple instance declared above.


If you want GHC to choose the most specific instance (which would be 
your first one for tuples), use the


{-# LANGUAGE OverlappingInstances #-}

pragma. Be careful with this however, as it might lead to unexpected 
results. For a similar problem, you may want to consult the haskell wiki[1].


-- Steffen

[1] http://haskell.org/haskellwiki/GHC/AdvancedOverlap

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


Re: [Haskell-cafe] Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker



On 06/26/2011 04:16 PM, michael rice wrote:

MathWorks has the function seqperiod(x) to return the period of sequence
x. Is there an equivalent function in Haskell?


Could you specify what exactly the function is supposed to do? I am 
pretty sure that a function like


seqPeriod :: (Eq a) = [a] - Maybe Integer  -- Nothing iff non-periodic

cannot be written. If sequences are represented by the terms that 
define them (or this information is at least accessible), chances might 
be better, but I would still be interested how such a function works. 
The problem seems undecidable to me in general.


On finite lists (which may be produced from infinite ones via 'take'), a 
naive implementation could be this:



 import Data.List (inits, cycle, isPrefixOf)
 import Debug.Trace

 -- Given a finite list, calculate its period.
 -- The first parameter controls what is accepted as a generator. See 
below.

 -- Set it to False when looking at chunks from an infinite sequence.
 listPeriod :: (Eq a) = Bool - [a] - Int
 listPeriod precisely xs = case filter (generates precisely xs) (inits 
xs) of

 -- as (last $ init xs) == xs, this will always suffice.
 (g:_) - length g  -- length of the *shortest* generator

 -- @generates prec xs g@ iff @g@ generates @xs@ by repitition. If 
@prec@, the

 -- lengths have to match, too. Consider
 --
 --  generates True [1,2,3,1,2,1,2] [1,2,3,1,2]
 -- False
 --
 --  generates False [1,2,3,1,2,1,2] [1,2,3,1,2]
 -- True
 generates :: (Eq a) = Bool - [a] - [a] - Bool
 generates precisely xs g = if null g
 then null xs
 else (not precisely || length xs `mod` length g == 0)
xs `isPrefixOf` cycle g


-- Steffen

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


[Haskell-cafe] Fwd: Re: Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker


Forwarding to -cafe

 Original Message 
Subject:Re: [Haskell-cafe] Period of a sequence
Date:   Mon, 27 Jun 2011 04:46:10 -0700 (PDT)
From:   michael rice nowg...@yahoo.com
To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de



Hi Steffen,

Repeating decimals.

5/7 == 0.714285 714285 7142857 ... Period = 6

It does seem like a difficult problem.

This one is eventually repeating, with Period = 3

3227/555 = 5.8144 144 144…

Michael

--- On *Mon, 6/27/11, Steffen Schuldenzucker
/sschuldenzuc...@uni-bonn.de/*wrote:


From: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de
Subject: Re: [Haskell-cafe] Period of a sequence
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Monday, June 27, 2011, 4:32 AM



On 06/26/2011 04:16 PM, michael rice wrote:
  MathWorks has the function seqperiod(x) to return the period of
sequence
  x. Is there an equivalent function in Haskell?

Could you specify what exactly the function is supposed to do? I am
pretty sure that a function like

seqPeriod :: (Eq a) = [a] - Maybe Integer -- Nothing iff non-periodic

cannot be written. If sequences are represented by the terms that
define them (or this information is at least accessible), chances
might be better, but I would still be interested how such a function
works. The problem seems undecidable to me in general.

On finite lists (which may be produced from infinite ones via
'take'), a naive implementation could be this:

 
  import Data.List (inits, cycle, isPrefixOf)
  import Debug.Trace
 
  -- Given a finite list, calculate its period.
  -- The first parameter controls what is accepted as a generator.
See below.
  -- Set it to False when looking at chunks from an infinite sequence.
  listPeriod :: (Eq a) = Bool - [a] - Int
  listPeriod precisely xs = case filter (generates precisely xs)
(inits xs) of
  -- as (last $ init xs) == xs, this will always suffice.
  (g:_) - length g -- length of the *shortest* generator
 
  -- @generates prec xs g@ iff @g@ generates @xs@ by repitition. If
@prec@, the
  -- lengths have to match, too. Consider
  --
  --  generates True [1,2,3,1,2,1,2] [1,2,3,1,2]
  -- False
  --
  --  generates False [1,2,3,1,2,1,2] [1,2,3,1,2]
  -- True
  generates :: (Eq a) = Bool - [a] - [a] - Bool
  generates precisely xs g = if null g
  then null xs
  else (not precisely || length xs `mod` length g == 0)
   xs `isPrefixOf` cycle g
 

-- Steffen


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


Re: [Haskell-cafe] Fwd: Re: Period of a sequence

2011-06-27 Thread Steffen Schuldenzucker


Michael,

On 06/27/2011 01:51 PM, Steffen Schuldenzucker wrote:

 Forwarding to -cafe

  Original Message 
 Subject: Re: [Haskell-cafe] Period of a sequence
 Date: Mon, 27 Jun 2011 04:46:10 -0700 (PDT)
 From: michael rice nowg...@yahoo.com
 To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de

 Hi Steffen,

 Repeating decimals.

 5/7 == 0.714285 714285 7142857 ... Period = 6

 It does seem like a difficult problem.

 This one is eventually repeating, with Period = 3

 3227/555 = 5.8144 144 144…

why not use the well-known division algorithm: (I hope this is readable)

3227 / 555
= 3227 `div` 555 + 3227 `mod` 555 / 555
= 5 + 452 / 555
= 5 + 0.1 * 4520 / 555
= 5 + 0.1 * (4520 `div` 555 + (4520 `mod` 555) / 555)
= 5 + 0.1 * (8 + 80 / 555)
= 5 + 0.1 * (8 + 0.1 * (800 / 555))
= 5 + 0.1 * (8 + 0.1 * (800 `div` 555 + (800 `mod` 555) / 555))
= 5 + 0.1 * (8 + 0.1 * (1 + 245 / 555))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * 2450 / 555))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * (4 + 230 / 555)))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * (4 + 0.1 * 2300 / 555)))
= 5 + 0.1 * (8 + 0.1 * (1 + 0.1 * (4 + 0.1 * (4 + 80 / 555
*whoops*, saw 80 already, namely in line 6. Would go on like that 
forever if I continued like this, so the final result has to be:


vvv Part before the place where I saw the '80' first
5.8 144 144 144 ...
^^^ Part after I saw the '80'

So you could write a recursive function that takes as an accumulating 
parameter containing the list of numbers already seen:


-- periodOf n m gives the periodic part of n/m as a decimal fraction.
-- (or an empty list if that number has finitely many decimal places)
 periodOf :: (Integral a) = a - a - [a]
 periodOf = periodOfWorker []
   where
 periodOfWorker seen n m
 | n `mod` m == 0 = ...
 | (n `mod` m) `elem` seen = ...
 | otherwise = ...


--- On *Mon, 6/27/11, Steffen Schuldenzucker
/sschuldenzuc...@uni-bonn.de/*wrote:


From: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de
Subject: Re: [Haskell-cafe] Period of a sequence
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Monday, June 27, 2011, 4:32 AM



On 06/26/2011 04:16 PM, michael rice wrote:
  MathWorks has the function seqperiod(x) to return the period of
sequence
  x. Is there an equivalent function in Haskell?

Could you specify what exactly the function is supposed to do? I am
pretty sure that a function like

seqPeriod :: (Eq a) = [a] - Maybe Integer -- Nothing iff non-periodic

cannot be written. If sequences are represented by the terms that
define them (or this information is at least accessible), chances
might be better, but I would still be interested how such a function
works. The problem seems undecidable to me in general.

On finite lists (which may be produced from infinite ones via
'take'), a naive implementation could be this:

 
  import Data.List (inits, cycle, isPrefixOf)
  import Debug.Trace
 
  -- Given a finite list, calculate its period.
  -- The first parameter controls what is accepted as a generator.
See below.
  -- Set it to False when looking at chunks from an infinite sequence.
  listPeriod :: (Eq a) = Bool - [a] - Int
  listPeriod precisely xs = case filter (generates precisely xs)
(inits xs) of
  -- as (last $ init xs) == xs, this will always suffice.
  (g:_) - length g -- length of the *shortest* generator
 
  -- @generates prec xs g@ iff @g@ generates @xs@ by repitition. If
@prec@, the
  -- lengths have to match, too. Consider
  --
  --  generates True [1,2,3,1,2,1,2] [1,2,3,1,2]
  -- False
  --
  --  generates False [1,2,3,1,2,1,2] [1,2,3,1,2]
  -- True
  generates :: (Eq a) = Bool - [a] - [a] - Bool
  generates precisely xs g = if null g
  then null xs
  else (not precisely || length xs `mod` length g == 0)
   xs `isPrefixOf` cycle g
 

-- Steffen


___
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] Hackage Server not reachable

2011-06-22 Thread Steffen Schuldenzucker



On 06/22/2011 11:02 AM, Stuart Coyle wrote:

I cannot reach the hackage server so cabal can't download packages.

Have I the correct address?
http://hackage.haskell.org


Yes.



stuart@rumbaba:~# resolveip hackage.haskell.org http://hackage.haskell.org
IP address of hackage.haskell.org http://hackage.haskell.org is
69.30.63.204


Same result for me.



I also cannot access any of the Hackage web pages.


No problem here.

What is the error for you? hackage.haskell.org doesn't seem to answer 
pings btw.


-- Steffen

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


[Haskell-cafe] Fwd: Re: Hackage Server not reachable

2011-06-22 Thread Steffen Schuldenzucker


Forwarding to -cafe.

 Original Message 
Subject:Re: [Haskell-cafe] Hackage Server not reachable
Date:   Wed, 22 Jun 2011 20:43:59 +1000
From:   Stuart Coyle stuart.co...@gmail.com
To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de



Cabal fails with a timeout like this:

stuart@Panforte:~/Code/gift-parser# cabal update
Downloading the latest package list from hackage.haskell.org
http://hackage.haskell.org
cabal: timeout

 From traceroute it seems that I'm having routing problems.

traceroute to hackage.haskell.org http://hackage.haskell.org
(69.30.63.204), 64 hops max, 52 byte packets
  1  moodle-server (192.168.1.1)  1.834 ms  0.923 ms  0.904 ms
  2  10.67.0.1 (10.67.0.1)  18.781 ms  10.031 ms  14.738 ms
  3 rdl2-ge2.gw.optusnet.com.au http://rdl2-ge2.gw.optusnet.com.au
(198.142.160.5)  13.442 ms  11.920 ms  8.767 ms
  4 mas2-ge10-1-0-904.gw.optusnet.com.au
http://mas2-ge10-1-0-904.gw.optusnet.com.au (211.29.125.138)  55.286
ms  56.473 ms  58.150 ms
  5 mas3-ge11-0.gw.optusnet.com.au
http://mas3-ge11-0.gw.optusnet.com.au (211.29.125.241)  61.473 ms
  58.477 ms  56.198 ms
  6  203.208.192.169 (203.208.192.169)  202.737 ms  207.018 ms  209.159 ms
  7 lap-brdr-03.inet.qwest.net http://lap-brdr-03.inet.qwest.net
(63.146.26.145)  173.527 ms  174.207 ms
lap-brdr-03.inet.qwest.net http://lap-brdr-03.inet.qwest.net
(63.146.26.149)  172.122 ms
  8 tuk-edge-13.inet.qwest.net http://tuk-edge-13.inet.qwest.net
(67.14.4.206)  235.820 ms  237.548 ms  246.359 ms
  9  206.81.193.22 (206.81.193.22)  334.748 ms  511.734 ms  303.460 ms
10  209.162.220.81 (209.162.220.81)  310.886 ms  244.478 ms  241.544 ms
11  * * *
12  * * *
13  * * *
continues like this

  I'll get a fix from this end. Time to call the ISP.
I wonder if any others in Australia on Optus' network are having the
same issue?

Thanks all.

On Wed, Jun 22, 2011 at 7:16 PM, Steffen Schuldenzucker
sschuldenzuc...@uni-bonn.de mailto:sschuldenzuc...@uni-bonn.de wrote:



On 06/22/2011 11:02 AM, Stuart Coyle wrote:

I cannot reach the hackage server so cabal can't download packages.

Have I the correct address?
http://hackage.haskell.org


Yes.


stuart@rumbaba:~# resolveip hackage.haskell.org
http://hackage.haskell.org http://hackage.haskell.org
IP address of hackage.haskell.org http://hackage.haskell.org
http://hackage.haskell.org is
69.30.63.204


Same result for me.



I also cannot access any of the Hackage web pages.


No problem here.

What is the error for you? hackage.haskell.org
http://hackage.haskell.org doesn't seem to answer pings btw.

-- Steffen




--
Stuart Coyle
stuart dot coyle at gmail dot com




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


Re: [Haskell-cafe] Are casts required?

2011-06-06 Thread Steffen Schuldenzucker


Hi Patrick,

On 06/06/2011 09:45 AM, Patrick Browne wrote:

Are casts required to run the code below?
If so why?
Thanks,
Pat


-- Idetifiers for objects
class (Integral i) =  IDs i where
  startId :: i
  newId :: i -  i
  newId i = succ i
  sameId, notSameId :: i -  i -  Bool
-- Assertion is not easily expressible in Haskell
-- notSameId i newId i  = True
  sameId i j = i == j
  notSameId i j = not (sameId i j)
  startId = 1


instance IDs Integer where



-- are casts need here?
sameId (newId startId::Integer) 3


I'll take this as an example. First of all, note that

WHAT YOU'VE WRITTEN IS NOT A CAST

, that is, if x is an Int, then x :: Double is a type error. What the 
'::' does is (in this situation) that it specializes the type of a 
polymorphic value.


In GHCi, omitting the ':: Integer' part, I get

*Main let x1' = sameId (newId startId) 3

interactive:1:10:
Ambiguous type variable `i' in the constraint:
  `IDs i' arising from a use of `sameId' at interactive:1:10-33
Probable fix: add a type signature that fixes these type variable(s)

Let's take the above expression apart:

We have:

*Main :t newId startId
newId startId :: (IDs i) = i

*Main :t 3
3 :: (Num t) = t

*Main :t sameId
sameId :: (IDs i) = i - i - Bool

Now, when trying to evaluating your expression, the machine ultimately 
has to know what (newId startId) and 3 are. This, of course, depends on 
the type chosen for i and t, respectively.

For example, if I define the following instance:

instance IDs Int where
startId = 2

we have:

*Main sameId (newId startId :: Integer) 3
False
*Main sameId (newId startId :: Int) 3
True

, so the result type clearly depends on the types chosen.
But, lacking an explicit signature, there is no way for the machine to 
tell which types should be used, in particular as the information which 
types were chosen is completely lost in the resulting type 'Bool'.


The example above does not look as if it was created to illustrate your 
problem. Then however, note that you don't have to use a class if you 
don't expect people to overwrite your default implementations. Normal 
Functions are sufficient:


 -- I always want this
 {-# LANGUAGE NoMonomorphismRestriction #-}

 startId :: (Integral i) = i
 startId = 1

 newId :: (Integral i) = i - i
 newId = succ

 sameId, notSameId :: (Integral i) = i - i - Bool
 sameId = (==)
 notSameId i j = not $ sameId i j

Ok, now this works even without the signatures:

*Main sameId (newId startId) 3
False

, which is probably caused by defaulting on the top level (IIRC, an 
unresolved Integral type variable defaults to Integer. Don't have the 
documentation at hand right now.) like this:


*Main let i3 = 3 :: (Integral x = x)
*Main :t i3
i3 :: Integer

and the same thing happens on the (newId startId) side, too.

As one last remark, your original problem that caused the Ambiguous 
type variable error looks very similar to the well-known (show . read) 
problem.


-- Steffen

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


Re: [Haskell-cafe] Comment Syntax

2011-06-03 Thread Steffen Schuldenzucker



Am 03.06.2011 10:32, schrieb Guy:
What might --| mean, if not a comment? It doesn't seem possible to 
define it as an operator.
Obviously, anyone who is going to write a formal logic framework would 
want to define the following operators ;) :


T |- phi: T proves phi
T |-- phi: T proves phi directly (by application of a single rule)
phi -| T: phi is proven by T
phi --| T: phi is proven by T directly

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


Re: [Haskell-cafe] Server hosting

2011-05-06 Thread Steffen Schuldenzucker

On 05/06/2011 08:07 PM, Andrew Coppin wrote:

[...]
I currently have a website, but it supports only CGI *scripts* (i.e.,
Perl or PHP). It does not support arbitrary CGI *binaries*, which is
what I'd want for Haskell. In fact, I don't have control over the web
server at all; I just put content on there.


I don't really expect this to work, but...

?php

$argsstr = ...
$ok = 0
passthru( './my_real_cgi '.$argsstr, $ok );
exit( $ok );

?

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


Re: [Haskell-cafe] A small Darcs anomoly

2011-04-28 Thread Steffen Schuldenzucker


On 04/28/2011 05:23 PM, malcolm.wallace wrote:

Unfortunately, sharing a build directory between separate repositories
does not work. After a build from one repository, all the outputs from
that build will have modification times more recent than all the files
in the other repository.

Then I suggest that your build tools are broken. Rebuilding should not
depend on an _ordering_ between modification times of source and object,
merely on whether the timestamp of the source file is different to its
timestamp the last time we looked. (This requires your build tools to
keep a journal/log, yes, but it is the only safe way to do it.)


So 'make' is broken (in this regard)? Then - I fear - everyone has to 
cope with that.


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


Re: [Haskell-cafe] Generating random graph

2011-04-10 Thread Steffen Schuldenzucker


Hello.

I don't know if that is the reason for the strange behaviour, but

On 04/11/2011 03:03 AM, Mitar wrote:

I have made this function to generate a random graph for
Data.Graph.Inductive library:

generateGraph :: Int -  IO (Gr String Double)
generateGraph graphSize = do
   when (graphSize  1) $ throwIO $ AssertionFailed $ Graph size out
of bounds  ++ show graphSize
   let ns = map (\n -  (n, show n)) [1..graphSize]
   es- fmap concat $ forM [1..graphSize] $ \node -  do
 nedges- randomRIO (0, graphSize)
 others- fmap (filter (node /=) . nub) $ forM [1..nedges] $ \_ -
randomRIO (1, graphSize)
 gen- getStdGen
 let weights = randomRs (1, 10) gen


^ this use of randomRs looks wrong.


 return $ zip3 (repeat node) others weights
   return $ mkGraph ns es


http://hackage.haskell.org/packages/archive/random/latest/doc/html/System-Random.html

tells me:

  randomRs :: RandomGen g = (a, a) - g - [a]

  Plural variant of randomR, producing an infinite list of random
  values instead of returning a new generator.

So when using randomRs, the state of the global random number generator 
is not updated, but it is used again in the next iteration of the 
toplevel forM [1..graphSize] loop. Try:


 weights - replicateM (length others) $ randomRIO (1, 10)

instead.

-- Steffen



But I noticed that graph has sometimes same weights on different
edges. This is very unlikely to happen so probably I have some error
using random generators. Could somebody tell me where?


Mitar

___
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] object oriented technique

2011-03-29 Thread Steffen Schuldenzucker


Tad,

It doesn't look bad, but depending on what you want to do with the
[ShapeD] aftewards you might not need this level of generality.

Remember that the content of a ShapeD has type (forall a. ShapeC a =
a), so all you can do with it is call class methods from ShapeC. So if
all you do is construct some ShapeD and pass that around, the following
solution is equivalent:

data Shape = Shape {
 draw :: String
 copyTo :: Double -  Double - Shape
 -- ^ We loose some information here. The original method of ShapeC
 -- stated that copyTo of a Rectangle will be a rectangle again
 -- etc. Feel free to add a proxy type parameter to Shape if this
 -- information is necessary.
}

circle :: Double - Double - Double - Shape
circle x y r = Shape dc $ \x y - circle x y r
  where dc = Circ ( ++ show x ++ ,  ++ show y ++ ) --  ++ show r

rectangle :: Double - Double - Double - Double - Shape
rectangle x y w h = ... (analogous)

shapes = [rectangle 1 2 3 4, circle 4 3 2, circle 1 1 1]

-- Steffen

On 03/29/2011 07:49 AM, Tad Doxsee wrote:

I've been trying to learn Haskell for a while now, and recently
wanted to do something that's very common in the object oriented
world, subtype polymorphism with a heterogeneous collection. It took
me a while, but I found a solution that meets my needs. It's a
combination of solutions that I saw on the web, but I've never seen
it presented in a way that combines both in a short note. (I'm sure
it's out there somewhere, but it's off the beaten path that I've been
struggling along.)  The related solutions are

1. section 3.6 of http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf

2. The GADT comment at the end of section 4 of
http://www.haskell.org/haskellwiki/Heterogenous_collections

I'm looking for comments on the practicality of the solution, and
references to better explanations of, extensions to, or simpler
alternatives for what I'm trying to achieve.

Using the standard example, here's the code:


data Rectangle = Rectangle { rx, ry, rw, rh :: Double } deriving (Eq,
Show)

drawRect :: Rectangle -  String drawRect r = Rect ( ++ show (rx r)
++ ,   ++ show (ry r) ++ ) --  ++ show (rw r) ++  x  ++ show
(rh r)


data Circle = Circle {cx, cy, cr :: Double} deriving (Eq, Show)

drawCirc :: Circle -  String drawCirc c = Circ ( ++ show (cx c) ++
,  ++ show (cy c)++ ) --  ++ show (cr c)

r1 = Rectangle 0 0 3 2 r2 = Rectangle 1 1 4 5 c1 = Circle 0 0 5 c2 =
Circle 2 0 7


rs = [r1, r2] cs = [c1, c2]

rDrawing = map drawRect rs cDrawing = map drawCirc cs

-- shapes = rs ++ cs

Of course, the last line won't compile because the standard Haskell
list may contain only homogeneous types.  What I wanted to do is
create a list of circles and rectangles, put them in a list, and draw
them.  It was easy for me to find on the web and in books how to do
that if I controlled all of the code. What wasn't immediately obvious
to me was how to do that in a library that could be extended by
others.  The references noted previously suggest this solution:


class ShapeC s where draw :: s -  String copyTo :: s -  Double -
Double -  s

-- needs {-# LANGUAGE GADTs #-} data ShapeD  where ShapeD :: ShapeC s
=  s -  ShapeD

instance ShapeC ShapeD where draw (ShapeD s) = draw s copyTo (ShapeD
s) x y = ShapeD (copyTo s x y)

mkShape :: ShapeC s =  s -  ShapeD mkShape s = ShapeD s



instance ShapeC Rectangle where draw = drawRect copyTo (Rectangle _ _
rw rh) x y = Rectangle x y rw rh

instance ShapeC Circle where draw = drawCirc copyTo (Circle _ _ r) x
y = Circle x y r


r1s = ShapeD r1 r2s = ShapeD r2 c1s = ShapeD c1 c2s = ShapeD c2

shapes1 = [r1s, r2s, c1s, c2s] drawing1 = map draw shapes1

shapes2 = map mkShape rs ++ map mkShape cs drawing2 = map draw
shapes2

-- copy the shapes to the origin then draw them shapes3 = map (\s -
copyTo s 0 0) shapes2 drawing3 = map draw shapes3


Another user could create a list of shapes that included triangles by
creating a ShapeC instance for his triangle and using mkShape to add
it to a list of ShapeDs.

Is the above the standard method in Haskell for creating an
extensible heterogeneous list of objects that share a common
interface?  Are there better approaches?  (I ran into a possible
limitation to this approach that I plan to ask about later if I can't
figure it out myself.)

- Tad

___ 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] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-12 Thread steffen
There is no SDK for older Mac OS X Releases in XCode 4, but for iPhone... 
Not even in the Resources/Packages.
Indeed Apple did remove support for older Systems then snow leopard in its 
new development tools.
For that reason and problems with no support of IB Plugins one is encouraged 
not to delete XCode 3.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-11 Thread steffen
ok, now I've installed XCode 4 and run into the very same problems.

As already said, XCode 4 targets snow leopard only. That's why the 
MacOSX10.5.sdk is missing. unfortunately the ghc packages for snow leopard 
are configured to support leopard still.

See: 
/Library/Frameworks/GHC.framework/Versions/Current/usr/share/doc/ghc/html/libraries/ghc-7.0.2/src/Config.html

So we either have to copy or symling /Developer-old/SDKs/MacOSX10.5.sdk to 
/Developer/SDKs or someone is going to recompile ghc with snow leopard only 
in mind.

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


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-10 Thread steffen
Hi,

I haven't installed XCode 4 yet, but the crt1.10.5.o is the c runtime file 
defining the symbol start which any program will be linked with being the 
programs real entry point.

Disassembling crt1.10.5.o (for Leopard) and crt1.10.6.o (for Snow 
Leopard) reveals the very same code for the symbol start, but
crt1.10.5.o additionally defines dyld_stub_binding_helper and 
__dyld_func_lookup.

I think I read that XCode 4 is snow leopard+ only, therefore I 
guess crt1.10.5.o was deleted when you've install Xcode 4.

Maybe a symbolic link ln -s crt1.10.6.o crt1.10.5.o in /usr/lib shall do 
just fine, but I will keep a copy of crt1.10.5.o before upgrading to Xcode 
4 just in case and report any findings.

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


Re: [Haskell-cafe] possible bug for ghc 7 + xcode 4 on snow leopard?

2011-03-10 Thread steffen
Questions:
1. How did you install ghc-7? Using a binary package? The one for leopard or 
snow leopard?
2. Which compiler flags did you use? Does it work with another backend?

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


Re: [Haskell-cafe] Having trouble with instance context

2011-02-23 Thread Steffen Schuldenzucker


Hi,

On 02/23/2011 04:40 PM, Kurt Stutsman wrote:
 [...]
 Test is actually a kind of Serializable class. I don't want to 
restrict it to only working with Enums, which is what your 
OverlappingInstances seems to address. Is there a better way for doing 
what I am trying to do?


Example:

import Data.BitSet

data GroupA = A1 | A2 | A3 deriving (Enum, Show)

data GroupB = B1 | B2  deriving (Enum, Show)

class Serializable t where
   get :: String - t
   put :: t - String

instance Enum e = Serializable e where
   get mask = {- convert mask to Int and then to a BitSet -}
   put bitset = {- convert BitSet to Int and then to String -}


You might want to use a wrapper type: (instead of the Serializable 
instance above)


{-# LANGUAGE GeneralizedNewtypeDeriving #-}

newtype ByEnum e = ByEnum { unByEnum :: e }
deriving (Eq, Ord, Read, Show, Enum)  -- just for convenience

instance Enum e = Serializable (ByEnum e) where
get = ByEnum . {- same code as above -}
put = {- same code as above -} . unByEnum

To see why this can't be done as you tried above, say that you have 
another instance of Serialize for types that are an instance of both 
Show an Read, serializing to/from a string using the 'show' and 'read' 
functions.


Then consider a type which is an instance of all Show, Read, and Enum, 
for example:


data Food = Meat | Vegetables deriving (Show, Read, Enum)

Which instance of Serializable should be used? The first one that was 
declared? Rather not...


An instance like

If (Enum t), then (Serializable t) via the Enum instance; else, if 
(Show t, Read t), then (Serializable t) via the Show and Read instances; 
otherwise not (Serializable t)


would be perfect, but unfortunately Haskell doesn't have a way to 
express this (yet?). Some steps[1] in this direction can however be 
taken with the current state of the language.


-- Steffen

[1] http://haskell.org/haskellwiki/GHC/AdvancedOverlap


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


Re: [Haskell-cafe] Proving correctness

2011-02-11 Thread Steffen Schuldenzucker

On 02/11/2011 12:06 PM, C K Kashyap wrote:

[...]
I know that static typing and strong typing of Haskell eliminate a 
whole class of problems - is that related to the proving correctness?

[...]
You might have read about free theorems arising from types. They are a 
method to derive certain properties about a value that must hold, only 
looking at its type. For example, a value


 x :: a

can't be anything else than bottom, a function

 f :: [a] - [a]

must commute with 'map', etc. For more information you may be interested 
in Theorems for free[1] by Philip Wadler.


[1] http://ttic.uchicago.edu/~dreyer/course/papers/wadler.pdf


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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Steffen Schuldenzucker


In ghci I get

 let evil = appendLog Foo Bar
interactive:1:11:
Ambiguous type variable `p' in the constraints:
  `PRead p'
arising from a use of `appendLog' at interactive:1:11-31
  `PWrite p'
arising from a use of `appendLog' at interactive:1:11-31
Probable fix: add a type signature that fixes these type variable(s)

And then, specializing evil's type:

 let good = appendLog Foo Bar :: Sealed Admin String
 unseal (undefined :: Admin) good
FooBar

-- Steffen

On 02/09/2011 06:15 PM, Cristiano Paris wrote:

Hi all,

I've a type problem that I cannot solve and, before I keep banging my
head against an unbreakable wall, I'd like to discuss it with the
list.

Consider the following code:


module Main where

class PRead p where {}
class PWrite p where {}

newtype Sealed p a = Sealed a

instance Monad (Sealed p) where
return = Sealed
(Sealed x)= f = f x

mustRead :: PRead p =  a -  Sealed p a
mustRead = Sealed

mustWrite :: PWrite p =  a -  Sealed p a
mustWrite = Sealed

readLog :: PRead p =  String -  Sealed p String
readLog = mustRead . id

writeLog :: PWrite p =  String -  Sealed p String
writeLog = mustWrite . id

appendLog l e = do l- readLog l
writeLog $ l ++ e


The central type of this code is Sealed, which boxes a value inside a
newtype with a phantom type which represents a set of permissions.

This set of permissions is implemented through a series of type
classes (PRead and PWrite in this case) which are attached to the
permission value p of the Sealed newtype.

This way I can define which set of permissions I expect to be enforced
when trying to peel off the Sealed value. The use of the Monad class
and type classes as permissions behaves nicely when combining
functions with different permission constraints, as it's the case of
appendLog, whose type signature is:

appendLog  :: (PRead p, PWrite p) =  String -  [Char] -  Sealed p String

Very nice, the permissions accumulates as constraints over the p type.
Now for the peel-off part:


unseal :: p -  Sealed p a -  a
unseal _ (Sealed x) = x


Basically this function requires a witness value of the type p to
peel-off the Sealed value. Notice that:


unseal undefined $ appendLog Foo Bar


won't work as the undefined value is unconstrained. That's good,
because otherwise it'd very easy to circumvent the enforcing
mechanism. So, I defined some roles:


data User = User
data Admin = Admin

instance PRead User where {}

instance PRead Admin where {}
instance PWrite Admin where {}


If I try to unseal the Sealed value passing User, it won't succeed, as
the type checker is expecting the value of a type which is also an
instance of the PWrite class:


*Main  unseal User $ appendLog Foo Bar

interactive:1:14:
 No instance for (PWrite User)
   arising from a use of `appendLog' atinteractive:1:14-34


while works perfectly if I pass Admin as a value:


*Main  unseal Admin $ appendLog Foo Bar
FooBar


The idea is to hide the Admin and User constructor from the programmer
and having two factory functions, checkAdmin and checkUser, which
checks whether the current user has the named role, something like:


checkAdmin :: IO Admin
checkUser :: IO User


where role checking happens in the IO Monad (or something similar),
a-là trusted kernel. So far so good and I'm very happy with that.

Now the problem.

I would like to enforce permissions not at the role level, but at the
permissions level. Let's say that I want to leave unseal unchanged,
I'd like to construct a p-value for unseal combining functions
checking for single permissions, that is, in pseudo-code:

unseal (checkPRead .*. checkPWrite) $ appendLog Foo Bar

where .*. is some kind of type aggregation operator.

Or maybe something like:

(checkPRead .*. checkPWrite) $ appendLog Foo Bar

So far I got only frustration. In principle it seems possible to
achieve this result because everything is known at compile time and
the type-checked should have all the information available to enforce
the security constraints.

Anyhow, I couldn't write any usable code.

Any help would be appreciated, even pointers to papers discussing this approach.

Thank you,




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


Re: [Haskell-cafe] Extending GHCi

2011-02-07 Thread Steffen Schuldenzucker

On 02/07/2011 12:45 PM, C K Kashyap wrote:



$ ghci
GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude :m +Data.IORef Control.Concurrent Control.Monad
Prelude Data.IORef Control.Concurrent Control.Monad msg -
newIORef Hello
Prelude Data.IORef Control.Concurrent Control.Monad let echo =
forever $ readIORef msg = putStrLn  threadDelay 300
Prelude Data.IORef Control.Concurrent Control.Monad t - forkIO echo
Hello
Prelude Data.IORef Control.Concurrent Control.Monad Hello
Hello
writeIORefHello msg World
Prelude Data.IORef Control.Concurrent Control.Monad World
World


On my mac, this works..but on Linux, the moment I do t - forkIO ... , 
it starts off a thread in the foreground and does not return to the 
prompt.

Strange. Works for me (ghc 6.12.1 on Debian squeeze).

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


Re: [Haskell-cafe] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker

On 02/04/2011 12:36 PM, C K Kashyap wrote:

Hi,
I am looking for a way to extend GHCI such that I can do something 
like this


$ ghci
GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude startMyFunction
Prelude

startMyFunction will do a forkIO and listen on a network port for 
interaction with a remote process and will drop back to GHCI prompt 
where I can invoke haskell functions that'll control the way the 
interaction with the remote process occurs. Can this be done?
I am not sure that I understand you correctly, but ghci simulates the IO 
monad, so what about:


Prelude :l MyModule.hs
*MyModule conn - waitForAndAcceptConnection
*MyModule someData - getSomeData conn
*MyModule sendSomeAnswer conn $ processSomeData someData
...

-- Steffen



Regards,
Kashyap


___
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] Extending GHCi

2011-02-04 Thread Steffen Schuldenzucker


Ok, so someFunction should modify the server's configuration? Maybe you 
can model it with an IORef like this (untested!):


 import Data.IORef

 type Config = String  -- String to be prepended to every answer

 someFunction :: String - IORef Config - IORef Config
 someFunction s r = modifyIORef s (++ s)

 startMyServer :: IO (IORef Config)
 startMyServer = do
 r - newIORef 
 forkIO $ runServer r
 return r

 runServer :: IORef - IO ()
 runServer r = do
 client - waitForAndAcceptConnection
 request - getSomeData client
 prep - readIORef r
 sendSomeAnswer client $ prep ++ request
 runServer r

And then:

*MyModule r - startMyServer
(plain echo server running)
*MyModule someFunction hello r
(now echo server with prepend hello)
*MyModule someFunction world r
(now echo server with prepend helloworld)

-- Steffen

On 02/04/2011 03:41 PM, C K Kashyap wrote:

Thanks Steffen,

Prelude :l MyModule.hs
*MyModule conn - waitForAndAcceptConnection
*MyModule someData - getSomeData conn
*MyModule sendSomeAnswer conn $ processSomeData someData
...


So this cycle of getting data from the connection and writing answer 
on the connection should happen concurrently with the ghci interaction 
... so lets say that when the thread is forked that listens on 
socket behaves like an echo server ... as in, it reads data from the 
client till \n and echoes it back ... All this would happen without 
the intervention of the user using GHCI ... However, using GHCI, the 
user should be able to modify the code such that the server returns 
hello prepended to the input. ..


 startMyServer -- at this point the the echo server gets spawned
   -- echo server continues to run
 someFunction hello --- now onwards  hello gets prepended
   --- echo server continues to run returning 
hello prepended

 someFunction world --- now onwards helloworld get

I hope this is possible without having to modify ghci itself.

Regards,
Kashyap


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


[Haskell-cafe] ($) not as transparent as it seems

2011-02-03 Thread Steffen Schuldenzucker


Dear cafe,

does anyone have an explanation for this?:

 error (error foo)
*** Exception: foo

 error $ error foo
*** Exception: *** Exception: foo

-- Steffen

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


Re: [Haskell-cafe] ($) not as transparent as it seems

2011-02-03 Thread Steffen Schuldenzucker


Thanks to all of you for making GHC's behaviour yet a bit clearer to me.

On 02/03/2011 11:25 PM, Daniel Fischer wrote:

On Thursday 03 February 2011 23:03:36, Luke Palmer wrote:
   

This is probably a result of strictness analysis.  error is
technically strict, so it is reasonable to optimize to:

 let e = error foo in e `seq` error e

 

I think so too.
Unoptimised,

module Errors where

foo = error (error foo)

bar = error $ error bar

produces the core

Errors.bar :: forall a_aaN. a_aaN
[GblId]
Errors.bar =
   \ (@ a_aaN) -
 GHC.Base.$
   @ [GHC.Types.Char]
   @ a_aaN
   (GHC.Err.error @ a_aaN)
   (GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# bar))

a_rb8 :: [GHC.Types.Char]
[GblId, Str=DmdType b]
a_rb8 =
   GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# foo)

Errors.foo :: forall a_aaP. a_aaP
[GblId]
Errors.foo =
   (\ (@ a_aaP) -  a_rb8)
   `cast` (forall a_aaP. CoUnsafe [GHC.Types.Char] a_aaP
   :: (forall a_aaP. [GHC.Types.Char]) ~ (forall a_aaP. a_aaP))
==

The first argument to ($) is evaluated before the second [because the
function may be lazy), resulting in the start of the error message
***Exception: , then that error-call must evaluate its argument, error
bar, which results in ***Exception: bar (and terminates the thread) and
two ***Exception:  being printed. If I interpret the core correctly,
error is so well known to the compiler that it strips off the outer `error'
in foo even without optimisations (which surprises me a bit).

With optimisations, ($) is inlined and `error $ error bar' is transformed
to error (error bar), from then on both have identical structure and
arrive at (mutatis mutandis) the same core (which is nearly the same as foo
got without optimisations).
   



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


Re: [Haskell-cafe] Typing problem

2011-01-31 Thread Steffen Schuldenzucker


Michael,

just leaving out the type declaration for 'normalize', your module 
complies fine and ghc infers the following type:


normalize :: (Integral a, Floating a) = [a] - a - a

Note that the context (Integral a, Floating a) cannot be met by any of 
the standard types. (try in ghci: :i Integral and :i Floating)
So we have to apply a conversion function like this: (I just replaced 
len by len' at all occurrences)


 normalize l = let (total,len) = sumlen l
  len' = fromIntegral len
  avg = total/len'
  stdev = sqrt $ ((/) (len'-1)) $ sum $ map ((** 2.0) 
. (subtract avg)) l

  in  ((/) stdev) . (subtract avg)

yielding a type of

normalize :: (Floating b) = [b] - b - b

You could save the conversion by allowing a more liberal type for 
'sumlen'. Without the type signature, it is inferred to


sumlen :: (Num t, Num t1) = [t] - (t, t1)

-- Steffen

On 01/31/2011 06:29 PM, michael rice wrote:

I'm mapping a function over a list of data, where the mapping function is
determined from the data.

g f l = map (g l) l

So

g serialize prolog  -  [4,5,3,2,3,1]

But I'm having typing problems trying to do a similar thing with a 
function

that statistically normalizes data.

See:
http://people.revoledu.com/kardi/tutorial/Similarity/Normalization.html#Statistic

So

g normalize [2,5,3,2]  -  
[-0.7071067811865475,1.414213562373095,0.0,-0.7071067811865475]


Is my typing for normalize too loose. Should I be using Floating 
rather than Num?


Michael

===Code==
{-
See Problem 42, pg. 63, Prolog by Example, Coelho  Cotta

Generate a list of serial numbers for the items of a given list,
the members of which are to be numbered in alphabetical order.

*Main serialize prolog
[4,5,3,2,3,1]
*Main serialize int.artificial
[5,7,9,1,2,8,9,5,4,5,3,5,2,6]

*Main [prolog] = serialize
[4,5,3,2,3,1]
*Main [int.artificial] = serialize
[5,7,9,1,2,8,9,5,4,5,3,5,2,6]
-}

import Data.Map hiding (map)
import Data.List

{-
serialize :: [Char] - [Int]
serialize l = map (f l) l
  where
f = ((!) . fromList . ((flip zip) [1..]) . (sort . nub))
-}

serialize :: (Ord a, Integral b) = [a] - a - b
serialize = ((!) . fromList . ((flip zip) [1..]) . (sort . nub))

g f l = map (f l) l

normalize :: (Num a, Num b) = [a] - a - b
normalize l = let (total,len) = sumlen l
  avg = total/len
  stdev = sqrt $ ((/) (len-1)) $ sum $ map ((** 2.0) . 
(subtract avg)) l

  in  ((/) stdev) . (subtract avg)

sumlen :: (Num a, Integral b) = [a] - (a,b)
sumlen l = sumlen' l 0 0
   where sumlen' [] sum len = (sum,len)
 sumlen' (h:t) sum len = sumlen' t (sum+h) (len+1)
=

Prelude :r
[1 of 1] Compiling Main ( serialize2.hs, interpreted )

serialize2.hs:34:32:
Could not deduce (Integral a) from the context (Num a, Num b)
  arising from a use of `sumlen' at serialize2.hs:34:32-39
Possible fix:
  add (Integral a) to the context of
the type signature for `normalize'
In the expression: sumlen l
In a pattern binding: (total, len) = sumlen l
In the expression:
let
  (total, len) = sumlen l
  avg = total / len
  stdev = sqrt
$   ((/) (len - 1)) $ sum $ map ((** 2.0) . (subtract 
avg)) l

in (/ stdev) . (subtract avg)

serialize2.hs:36:61:
Could not deduce (Floating a) from the context (Num a, Num b)
  arising from a use of `**' at serialize2.hs:36:61-66
Possible fix:
  add (Floating a) to the context of
the type signature for `normalize'
In the first argument of `(.)', namely `(** 2.0)'
In the first argument of `map', namely
`((** 2.0) . (subtract avg))'
In the second argument of `($)', namely
`map ((** 2.0) . (subtract avg)) l'

serialize2.hs:37:18:
Couldn't match expected type `b' against inferred type `a'
  `b' is a rigid type variable bound by
  the type signature for `normalize' at serialize2.hs:33:25
  `a' is a rigid type variable bound by
  the type signature for `normalize' at serialize2.hs:33:18
In the expression: (/ stdev) . (subtract avg)
In the expression:
let
  (total, len) = sumlen l
  avg = total / len
  stdev = sqrt
$   ((/) (len - 1)) $ sum $ map ((** 2.0) . (subtract 
avg)) l

in (/ stdev) . (subtract avg)
In the definition of `normalize':
normalize l = let
(total, len) = sumlen l
avg = total / len

  in (/ stdev) . (subtract avg)
Failed, modules loaded: none.



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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Inheritance and Wrappers

2011-01-31 Thread Steffen Schuldenzucker

On 01/31/2011 08:58 PM, MattMan wrote:

[...]

data Wrapper a = Wrap a
instance (Num a) =  AbGroup (Wrapper a) where
  add (Wrap i) (Wrap j) = Wrap(i+j)

However, this is clumsy.  Is there something else I can do?  Thanks
This is the normal approach. You can do funny things with the 
OverlappingInstances extension, but it is probably not what you want.


The problem is that the compiler only considers the heads of the 
instance declarations when determining which instance to use for a 
specific type. So an instance like this:


 instance (Num a) = AbGroup a where ...

means: Some type matching 'a' (that is, any type) is an instance of 
'AbGroup' if and only if it is an instance of 'Num'.


An additional instance like

 instance AbGroup SomeData where ...

would then conflict with the instance above: As 'SomeData' in particular 
matches the type 'a', the compiler does not know which one to choose. 
You could argue that the latter is more specific than the former, so 
the compiler should choose that one. This is exactly what 
OverlappingInstances does, but it can have more, unwanted effects.


You can make your wrapper code less clumsy by deriving some instances 
such as


 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 data Wrapper a = Wrap a deriving (Eq, Ord, Read, Show, Num)

-- Steffen



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


Re: [Haskell-cafe] Instantiation problem

2011-01-29 Thread Steffen Schuldenzucker


Hi,

Your definition of 'unit' in the

instance MetricDescription LengthInCentimetres Centimetre

is not well-typed. Maybe you want to write either

unit (LengthInCentimitres 2.0) = Centimetre
-- (pattern match fail for all (LengthInCentimetres l), l /= 2.0)

or

unit l = Centimetre
-- i.e. unit = const Centimetre as in the instance for Metre

Steffen


On 01/28/2011 12:42 PM, Patrick Browne wrote:

Below is some code that is produces information about the *types* used
for measuring (e.g. metres).  The following evaluation returns 1.00
which the convert factor for metres.

convertFactorToBaseUnit (unit (LengthInMetres  7))
.
The next evaluation returns the type, Metre, of data being measured
unit (LengthInMetres  7)

Using the particular definitions below is it possible to make an
instance of MetricDescription for centimetres? I have an error on the
defintion of the unit function in the definition of the
MetricDescription  instance.
As far as possible I would like to retain the data types and class
structures.


Thanks,
Pat

class (Unit unit) =  MetricDescription description unit | description -
unit where
  unit :: description -  unit
  valueInUnit :: description -  Double
  valueInBaseUnit :: description -  Double
  valueInBaseUnit d = (convertFactorToBaseUnit(unit d)) * (valueInUnit d)


data Metre = Metre  deriving Show
data Centimetre = Centimetre deriving Show

-- Each member of the Unit class has one operator convertFactorToBaseUnit
-- that takes a measurement unit (say metre) and returns a conversion
factor for that unit of measurement
class  Unit unit where
   convertFactorToBaseUnit :: unit -  Double

-- An instance for metres, where the convert factor is 1.0
instance Unit Metre where
  convertFactorToBaseUnit Metre  = 1.0

-- An instance for metres, where the convert factor is 0.1
instance Unit Centimetre where
   convertFactorToBaseUnit Centimetre  = 0.1



data LengthInMetres = LengthInMetres Double  deriving Show
data LengthInCentimetres = LengthInCentimetres Double  deriving Show

-- This seems fine
instance MetricDescription LengthInMetres Metre where
  valueInUnit (LengthInMetres d) = d
  unit l = Metre


-- This is the instance that I cannot get to work
-- The unit 2 function seems to be the problem.
-- instance MetricDescription LengthInCentimetres Centimetre where
--  valueInUnit (LengthInCentimetres d) = d
--  unit 2 = Centimetre


This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

___
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] combined parsing pretty-printing

2011-01-26 Thread Steffen Schuldenzucker

On 01/26/2011 05:22 PM, Ozgur Akgun wrote:
I working on a DSL represented by a algebraic data type with many 
constructors. I can write (separately) a parser and a pretty-printer 
for it, and I am doing so at the moment. However, this way it feels 
like repeating the same information twice.


Is there any work to combine the two?


You might want to take a look at [1, 2]XML Picklers from [3]HXT.

Steffen

[1] 
http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML

[2] http://blog.typlab.com/2009/11/writing-a-generic-xml-pickler/
[3] http://hackage.haskell.org/package/hxt-9.0.1



Best,
Ozgur


___
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] Tracing applied functions

2011-01-25 Thread steffen
did you try Debug.Trace?

http://haskell.org/ghc/docs/latest/html/libraries/base/Debug-Trace.html

On Jan 25, 3:39 am, Aaron Gray aaronngray.li...@gmail.com wrote:
 On 25 January 2011 02:12, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.comwrote:









  On 25 January 2011 12:05, Aaron Gray aaronngray.li...@gmail.com wrote:
   On 24 January 2011 23:01, Ivan Lazar Miljenovic 
  ivan.miljeno...@gmail.com
   wrote:

   On 25 January 2011 02:55, Aaron Gray aaronngray.li...@gmail.com wrote
Is there anyway to get a list of applied functions in the running of a
Haskell program ?

   Profile it?

   Okay, How do I do that ?

 http://www.haskell.org/haskellwiki/How_to_profile_a_Haskell_program
 http://book.realworldhaskell.org/read/profiling-and-optimization.html

 Thanks I will have a look at those in the morning.

 Aaron







   --
  Ivan Lazar Miljenovic
  ivan.miljeno...@gmail.com
  IvanMiljenovic.wordpress.com

 ___
 Haskell-Cafe mailing list
 Haskell-C...@haskell.orghttp://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] Tool for evaluating GHCi lines in a source file

2011-01-23 Thread Steffen Schuldenzucker


Hi,

some time ago I read of a small tool that extracts lines like GHCi 
some_expression from a source file and appends GHCi's output to them.

Now I can't find it again. Does anyone remember its name?

Thanks. Steffen

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


Re: [Haskell-cafe] Tool for evaluating GHCi lines in a source file

2011-01-23 Thread Steffen Schuldenzucker

On 01/23/2011 06:48 PM, Max Rabkin wrote:

On Sun, Jan 23, 2011 at 12:35, Steffen Schuldenzucker
sschuldenzuc...@uni-bonn.de  wrote:
   

Hi,

some time ago I read of a small tool that extracts lines like GHCi
some_expression from a source file and appends GHCi's output to them.
Now I can't find it again. Does anyone remember its name?
 

No, but I can guess (it's the same as the Python original, modulo
capitalisation):

http://hackage.haskell.org/package/DocTest
   


Exactly what I was looking for, thanks.


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


Re: [Haskell-cafe] Problem on overlapping instances

2011-01-05 Thread Steffen Schuldenzucker

Am 05.01.2011 09:24, schrieb Magicloud Magiclouds:

Hi,
   I am using Data.Binary which defined instance Binary a =  Binary
[a]. Now I need to define instance Binary [String] to make
something special for string list.
   How to make it work? I looked into the chapter of
overlappinginstances, nothing works.


Just a guess: Have you enabled TypeSynonymInstances? (As String is a 
type synonym, at least this extension would be required)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Managing multiple installations of GHC

2010-12-02 Thread steffen
 On Dec 1, 2010, at 8:38 PM, Antoine Latter wrote:

  If you're doing user installations of packages with 'cabal-install' it
  will take care of everything - all of the things that it installs are
  in per-GHC-version directories.
 ...
  Except for the haddock documentation that cabal-install installs -
  different versions of GHC/haddock are pretty much always breaking each
  other when I switch back and forth.

 This is because cabal's default layout *doesn't* install everything in 
 per-GHC-version directories. The layout is:

 prefix          -- /usr/local if --global, ~/.cabal if --user
   bin             -- binaries ($bindir)
   lib             -- ($libdir)
     pkgid
       compiler  -- libraries  .hi files ($libdir/$libsubdir, $dynlibdir)
         include   -- include files ($includedir)
   libexec         -- private binaries ($libexecdir)
   share           -- ($datadir)
     pkgid       -- data files ($datadir/$datasubdir)    
     doc
       pkgid     -- documentation ($docdir)
         html      -- html doc ($htmldir, $haddockdir)
     man           -- man pages ($mandir)

 Notice that only libraries, .hi files and includes are uner a per-compiler 
 directory. All the other things aren't, and as you notice they clobber each 
 other.

 I propose that the default in Cabal be changed to:

 prefix          -- /usr/local/haskell if --global, ~/.cabal if --user,
   compiler
     pkgid
       bin         -- binaries ($bindir)
       lib         -- libraries  .hi files ($libdir, $libdir/$libsubdir, 
 $dynlibdir)
         include   -- include files ($includedir)
       libexec     -- private binaries ($libexecdir)
       share       -- data files ($datadir, $datadir/$datasubdir)    
       doc         -- documentation ($docdir)
         html      -- html doc ($htmldir, $haddockdir)
         man       -- man pages ($mandir)
     bin           -- symlinks to binaries
     doc
       html        -- master index of html doc
       man         -- symlinks to man pages
   current         -- symlink to current compiler
   bin             -- symlink to current/bin      
   doc             -- symlink to current/doc

 This would put everything under a per-compiler top level dir, which is how 
 most other language systems install (for example perl and python both do it 
 this way) This would also allow very easy removal of an old compiler and 
 everything that was installed for it. Removing packages is also easier: you 
 just one pkgid dir per compiler to find and get rid of -- and you can do 
 it with a wildcard!

+1

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


[Haskell-cafe] Re: Manatee Video.

2010-11-30 Thread steffen
Hi Andy,

Can you please do something about the sound track? Loads of people are
not able to view your video, because the used content/sound track is
not available in every country... meaning youtube prohibits viewing
your video.

On 28 Nov., 17:30, Andy Stewart lazycat.mana...@gmail.com wrote:
 Hi all,

 Many people ask What's Manatee?

 A video worth a thousand words :
 here is video (select 720p HD)http://www.youtube.com/watch?v=weS6zys3U8k

 And i think the correct answer to What's Manatee? should be :
 Depend on you how to use it. :)

 Other information look :http://hackage.haskell.org/package/manatee

 Enjoy!

   -- Andy

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Manatee Video.

2010-11-30 Thread steffen
these links don't work either...
But there is an alternative video link to youko (http://v.youku.com/
v_show/id_XMjI2MDMzODI4.html) on the hackage page which works fine.

Looks interesting.
All those tabs and layout makes me wonder if manatee can become a
window manager of it's own. Say combining the launcher thing, Manatee
modes and window management into one application. Maybe by making
Manatee an opt in module for xmonad?!? Would this be possible?


On 30 Nov., 15:10, Andy Stewart lazycat.mana...@gmail.com wrote:
 steffen steffen.sier...@googlemail.com writes:
  Hi Andy,

  Can you please do something about the sound track? Loads of people are
  not able to view your video, because the used content/sound track is
  not available in every country... meaning youtube prohibits viewing
  your video.

 I will found some time upload a new video without sound.

 BTW, you can download video from below links:

 http://25.tel.115cdn.com/pickdown/M00/34/92/cWmqJkzxczoAFibVVCN3G...

 http://25.bak.115cdn.com/pickdown/11fec1f2ed229257059e426ab3c259714cf...

 Thanks for your suggestion. :)

   -- Andy











  On 28 Nov., 17:30, Andy Stewart lazycat.mana...@gmail.com wrote:
  Hi all,

  Many people ask What's Manatee?

  A video worth a thousand words :
  here is video (select 720p HD)http://www.youtube.com/watch?v=weS6zys3U8k

  And i think the correct answer to What's Manatee? should be :
  Depend on you how to use it. :)

  Other information look :http://hackage.haskell.org/package/manatee

  Enjoy!

    -- Andy

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

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: How to generalize executing a series of commands, based on a list?

2010-11-18 Thread steffen
1. Write one routine, which does all the work for just one command.
2. use sequence or mapM, mapM_ from Control.Monad (depending on your
needs),
   to apply your function to a list of commands

accumulating results you may want to process the output of sequence
or use the WriterT Monad Transformer.

If you want to stop processing the rest of the list on error, either
write a recursive function yourself or use foldM or use ErrorT Monad
Transformer.

On Nov 18, 3:03 am, Peter Schmitz ps.hask...@gmail.com wrote:
 I am able to use System.Cmd (system) to invoke a shell command
 and interpret the results.

 Please see the code below that works okay for one such command.
 (I invoke a program, passing two args.)

 I am wondering how to generalize this to do likewise for a
 series of commands, where the varying args (filenames, in this
 case) are in a list ('inOutLeafs').

 I will also want to accumulate some results; probably just a
 failure count at this time.

 Any advice or pointers to examples would be much appreciated.

 Thanks in advance,
 -- Peter









  run :: ... - IO (Int)    -- will return a fail count
  run
     -- some args to this function here...
     = do
        -- ... set up: inputLeafs, outputLeafs, etc.

        -- zip two lists of filenames:
        let inOutLeafs = zip inputLeafs outputLeafs

        -- the first pair for the first command:
        let (inFile1,outFile1) = head inOutLeafs

        -- build 1st command using 1st pair of filenames:
        let cmd1 = ...

        exitCode - system cmd1
        case (exitCode) of
           ExitSuccess - do
              putStrLn $ -- OK.
              return 0
           ExitFailure failCnt - do
              putStrLn $ -- Failed:  ++ show failCnt
              return 1

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


Re: Fwd: [Haskell-cafe] DSL libraries

2010-11-07 Thread steffen
Hey,

Sorry, hard week and I haven't had time to look into it until now. I
remember having had the very same Problem with AwesomePrelude. A very
quick fix for me was to remove the Lang.* and Compiler.* entries
in exposed-modules in the cabal file. You won't really need them
anyway.

If you really want to try AwesomePrelude, you may find the need to
changes some parts of it. For example, the AwesomePrelude's Num class
implies a Show instance, which can be very annoying. So best is to use
it as base for your own code and steal from it what you will need or
create your own version of AwesomePrelude according to your own
needs.

For example calling test in this example[1] will print out num and
when defining your own Show-Instance your program won't compile due to
overlapping instances.

The same example using AwesomePrelude with associated data families[2]
introducing new types for every aspect of your DSL  will look like [3]
(See the Lang.* Modules for more examples and evaluation, for this
kind of type safe DSL).

[1] https://gist.github.com/666119
[2] https://github.com/urso/AwesomePrelude
[3] https://gist.github.com/666121

On 4 Nov., 18:51, Dupont Corentin corentin.dup...@gmail.com wrote:
 Nobody had the compilation messages I had?







 -- Forwarded message --
 From: Dupont Corentin corentin.dup...@gmail.com
 Date: Tue, Nov 2, 2010 at 2:30 PM
 Subject: [Haskell-cafe] DSL libraries (Was: Map constructor in a DSL)
 To: steffen steffen.sier...@googlemail.com, haskell-c...@haskell.org

 Hello Steffen,
 can you compile AwesomePrelude?
 I've got error messages (see below).

 By the way, I've looked at some DSLs made in Haskell, if I don't mistake
 there are lots of similarities between them.
 There similarities could be put in a library to help the implementors of a
 DSL, more or less like AwesomePrelude.

 Is there already packages on Hackage dealing with that?

 Cheers,
 Corentin

 AwesomePrelude compilation error:
 I'm using GHC 6.12.1.

  cd tomlokhorst-AwesomePrelude-9819315
  cabal install
 (...)
 Warning: Lang.Haskell: Instances of type and data families are not yet
 supported. Instances of the following families will be filtered out:  H

 Then, when trying with a very simple GATD in GHCI, I've got:

 interactive: HSAwesomePrelude-0.1.0.o: unknown symbol
 `AwesomePreludezm0zi1zi0_
 CompilerziLiftDefinitions_inline_closure'
 ghc: unable to load package `AwesomePrelude-0.1.0'

 On Thu, Oct 28, 2010 at 2:02 PM, steffen 
 steffen.sier...@googlemail.comwrote:

  I think you would love to have a look at AwesomePrelude[1] or a fork
  of AwesomePrelude using associated types[2]
  Some more background information by Tom Lokhorst [3][4].

  [1]http://github.com/tomlokhorst/AwesomePrelude
  [2]http://github.com/urso/AwesomePrelude
  [3]http://tom.lokhorst.eu/2009/09/deeply-embedded-dsls
  [4]http://tom.lokhorst.eu/2010/02/awesomeprelude-presentation-video

  On 28 Okt., 12:09, Dupont Corentin corentin.dup...@gmail.com wrote:
   Thank you for your rich responses.

   Indeed I think I miss some thinks in my DSL, that would make things
  easier
   to deal with lists and first class functions.
   I don't really know what for now.
   Perhaps a List Constructor? Or a constructor on functions like yours
  Ryan?
   EAp :: Exp ref (a - b) - Exp ref a - Exp ref b
   It's from which DSL? It is accessible on the net?

   Chris suggested me that I can only define the Foldr constructor and
  deduce
   Map from it.
   But maybe I have to add a List constructor for that.

   But in the suggestions from Ryan and Brandon I don't understand why I
  should
   add an extra type parameter and what it is!

   Steffen: Wow nice. I'll integrate that ;)

   I'm also looking at the Atom's DSL to get inspiration.
   Something I don't understand in it is that it has two languages, on
  typed:

   data E a where
     VRef    :: V a - E a
     Const   :: a - E a
     Cast    :: (NumE a, NumE b) = E a - E b
     Add     :: NumE a = E a - E a - E a
   etc.

   And, along with it, an untyped counterpart:

   -- | An untyped term.
   data UE
     = UVRef UV
     | UConst Const
     | UCast  Type UE
     | UAdd   UE UE
   etc.

   What that for? What's the use of having beautiful GADT if you have to
   maintain an untyped ADT aside??

   Corentin

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



 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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 simplest extension language to implement?

2010-11-02 Thread Steffen Schuldenzucker

On 11/02/2010 10:40 AM, Yves Parès wrote:
Because he would have either to recompile the whole program or to use 
things like hint, both implying that GHC must be installed on the user 
side (600Mo+ for GHC 6.12.3)
Isn't there a way to use some stripped-down version of ghc and the base 
libraries, providing only what the user really needs, in versions which 
are known to work, and supply that together with the application?


I'd love to use haskell as a configuration language, provide some 
combinators and effectively get the rest for free.
But it is not acceptable for a user to go through the mess of installing 
a ghc environment on, say, Windows, only to change some settings.



2010/11/2 Lennart Augustsson lenn...@augustsson.net 
mailto:lenn...@augustsson.net


I don't understand.  Why don't you use Haskell as the scripting
language?

On Tue, Nov 2, 2010 at 7:04 AM, Permjacov Evgeniy
permea...@gmail.com mailto:permea...@gmail.com wrote:
 Let us think, that we need some scripting language for our pure
haskell
 project and configure-compile-run is not a way. In such a case a
 reasonably simple, yet standartized and wide known language
should be
 implemented. What such language may be?
  R(4/5/6)RS ?
  EcmaScript ?
  Some other ?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto: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] Am I using type families well?

2010-11-01 Thread Steffen Schuldenzucker
Hi Yves,

On 11/01/2010 09:44 PM, Yves Parès wrote:
 Yes, I did make a small mistake in the type of eval.
 In fact, through the compiler messages, I guessed that it was a problem of
 matching between the 'rsc' type variable of runLoader and the 'rsc' of eval.
 I thought that this kind of matching was automatic in Haskell, well I was
 wrong... Thanks !

Just out of curiosity: Does it work if you omit eval's type signature?

-- Steffen

 
 
 2010/11/1 Sjoerd Visscher sjo...@w3future.com mailto:sjo...@w3future.com
 
 Hi,
 
 There's nothing wrong with your type families. The problem is that the
 compiler doesn't know that the m and rsc of eval are the same as m and rsc
 of runLoader. (Also you had a small bug in the type of eval)
 
 You need the ScopedTypeVariables extension, with a forall on runLoader to
 tell GHC that they should be scoped:
 
 runLoader :: forall m rsc a. (Monad m, Resource rsc) = CfgOf (IdOf rsc)
 - RscLoader rsc m a - m a
 runLoader cfg loader = viewT loader = eval M.empty
  where
eval :: (Monad m, Resource rsc) =
 M.Map (IdOf rsc) rsc
 - ProgramViewT (EDSL (IdOf rsc)) m a
 - m a
eval _(Return x) = return x
eval rscs (instr := k) = case instr of
  Load id - do let loc = retrieveLoc cfg id
  -- open and load from loc will go here
  viewT (k ()) = eval rscs
  -- -- -- Other cases yet to come...
 
 greetings,
 Sjoerd
 
 
 On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:
 
  Hello,
 
  I'm trying to make a simple monad (built on operational's ProgramT) for
 resource loading.
  I have classes featuring type families :
 
  {-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
 
  -- | A ResourceId is something that identifies a resource.
  -- It should be unique for one resource, and should be used to find the
 location (the path) of the resource,
  -- possibly by using a configuration datatype
  class (Ord id) = ResourceId id where
type LocOf id
type CfgOf id
retrieveLoc :: CfgOf id - id - LocOf id
 
  -- | Class describing a resource of type @rsc@
  class (ResourceId (IdOf rsc)) = Resource rsc where
type IdOf rsc
load   :: LocOf (IdOf rsc) - IO (Maybe rsc)
  -- ^ Called when a resource needs to be loaded
unload :: rsc - IO ()
  -- ^ Idem for unloading
 
  -- | Then, the operations that the loader can perform
  data EDSL id a where
Load :: id - EDSL id ()
IsLoaded :: id - EDSL id Bool
Unload   :: id - EDSL id ()
 
  -- | The loader monad itself
  type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
 
  -- | And finally, how to run a loader
  runLoader :: (Monad m, Resource rsc) = CfgOf (IdOf rsc) - RscLoader
 rsc m a - m a
  runLoader cfg loader = viewT loader = eval M.empty
where
  eval :: (Monad m, Resource rsc) =
   M.Map (IdOf rsc) rsc
   - ProgramViewT (EDSL rsc) m a
   - m a
  eval _(Return x) = return x
  eval rscs (instr := k) = case instr of
Load id - do let loc = retrieveLoc cfg id
-- open and load from loc will go here
viewT (k ()) = eval rscs
-- -- -- Other cases yet to come...
 
 
 
  Well, there is no way I can get it type-check. I think I must be
 misusing the type families (I tried with multi-param typeclasses and
 functional dependencies, but it ends up to be the same kind of 
 nightmare...).
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 --
 Sjoerd Visscher
 sjo...@w3future.com mailto:sjo...@w3future.com
 
 
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Re: State nested structures

2010-10-29 Thread steffen

 Horribly enough this one seems to work...

 mapOnBofA :: SB a - SA a
 mapOnBofA mf = get = \st@(A {b=temp}) -
                let (ans,temp2) = runState mf temp
                in put (st { b=temp2})  return ans


There is nothing horrible about that. You just run a new isolated
computation in the State Monad for B and use its results. More or less
see same solution as Dupont's.

@Dupont:
telling from your possible use case and your last post with your MAP-
Problem, these two are very similar. You have a monad and inside your
monad you temporarily want to run some computation in another Monad. I
think Monad-Transformers are maybe the better option for you
(especially your interpreter-Problem was a good use case for StateT/
ErrorT instead of State and some Either inside it...).

On 29 Okt., 17:35, Stephen Tetley stephen.tet...@gmail.com wrote:
 2010/10/29 Dupont Corentin corentin.dup...@gmail.com:

  Also, I can't manage to write the more generic function SB x -  SA x.

 However, I'd have to question why you want both SA and SB as state
 functional types. Having inner runState's is sometimes good practice
 (its an instance of the Local Effect pattern identified by Ralf
 Laemmel and Joost Visser), but if you have it commonly I'd suspect
 you design is somehow contrived and could be simplified.
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: State nested structures

2010-10-29 Thread steffen
Nothing hinders you writing:

StateT Game (StateT A IO)

or

GameT mt = ErrorT Err (StateT Game (mt IO))
with mt being another Monad-Transformer

Monad-Transformers can be quite tricky. The point is you don't have to
create new Monad instances.

On 29 Okt., 18:46, Dupont Corentin corentin.dup...@gmail.com wrote:
 Thank you for your responses. I will look at monad transformers.
 I already use them I think because actually I use something like StateT Game
 IO a.
 You mean I have to implement my own instance?

 Oh, can you call me Corentin? This is my name ;)

 Cheers,
 Corentin

 On Fri, Oct 29, 2010 at 6:19 PM, steffen 
 steffen.sier...@googlemail.comwrote:









   Horribly enough this one seems to work...

   mapOnBofA :: SB a - SA a
   mapOnBofA mf = get = \st@(A {b=temp}) -
                  let (ans,temp2) = runState mf temp
                  in put (st { b=temp2})  return ans

  There is nothing horrible about that. You just run a new isolated
  computation in the State Monad for B and use its results. More or less
  see same solution as Dupont's.

  @Dupont:
  telling from your possible use case and your last post with your MAP-
  Problem, these two are very similar. You have a monad and inside your
  monad you temporarily want to run some computation in another Monad. I
  think Monad-Transformers are maybe the better option for you
  (especially your interpreter-Problem was a good use case for StateT/
  ErrorT instead of State and some Either inside it...).

  On 29 Okt., 17:35, Stephen Tetley stephen.tet...@gmail.com wrote:
   2010/10/29 Dupont Corentin corentin.dup...@gmail.com:

Also, I can't manage to write the more generic function SB x -  SA x.

   However, I'd have to question why you want both SA and SB as state
   functional types. Having inner runState's is sometimes good practice
   (its an instance of the Local Effect pattern identified by Ralf
   Laemmel and Joost Visser), but if you have it commonly I'd suspect
   you design is somehow contrived and could be simplified.
   ___
   Haskell-Cafe mailing list
   haskell-c...@haskell.orghttp://
 www.haskell.org/mailman/listinfo/haskell-cafe
   ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: State nested structures

2010-10-29 Thread steffen
you can find a nice introduction on using monad transformers by
developing an interpreter at [1] and a little more detailed one at [2]

[1]http://www.grabmueller.de/martin/www/pub/Transformers.pdf
[2]http://www.haskell.org/all_about_monads/html/

On 29 Okt., 18:46, Dupont Corentin corentin.dup...@gmail.com wrote:
 Thank you for your responses. I will look at monad transformers.
 I already use them I think because actually I use something like StateT Game
 IO a.
 You mean I have to implement my own instance?

 Oh, can you call me Corentin? This is my name ;)

 Cheers,
 Corentin

 On Fri, Oct 29, 2010 at 6:19 PM, steffen 
 steffen.sier...@googlemail.comwrote:









   Horribly enough this one seems to work...

   mapOnBofA :: SB a - SA a
   mapOnBofA mf = get = \st@(A {b=temp}) -
                  let (ans,temp2) = runState mf temp
                  in put (st { b=temp2})  return ans

  There is nothing horrible about that. You just run a new isolated
  computation in the State Monad for B and use its results. More or less
  see same solution as Dupont's.

  @Dupont:
  telling from your possible use case and your last post with your MAP-
  Problem, these two are very similar. You have a monad and inside your
  monad you temporarily want to run some computation in another Monad. I
  think Monad-Transformers are maybe the better option for you
  (especially your interpreter-Problem was a good use case for StateT/
  ErrorT instead of State and some Either inside it...).

  On 29 Okt., 17:35, Stephen Tetley stephen.tet...@gmail.com wrote:
   2010/10/29 Dupont Corentin corentin.dup...@gmail.com:

Also, I can't manage to write the more generic function SB x -  SA x.

   However, I'd have to question why you want both SA and SB as state
   functional types. Having inner runState's is sometimes good practice
   (its an instance of the Local Effect pattern identified by Ralf
   Laemmel and Joost Visser), but if you have it commonly I'd suspect
   you design is somehow contrived and could be simplified.
   ___
   Haskell-Cafe mailing list
   haskell-c...@haskell.orghttp://
 www.haskell.org/mailman/listinfo/haskell-cafe
   ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: Map constructor in a DSL

2010-10-28 Thread steffen
I think you would love to have a look at AwesomePrelude[1] or a fork
of AwesomePrelude using associated types[2]
Some more background information by Tom Lokhorst [3][4].

[1] http://github.com/tomlokhorst/AwesomePrelude
[2] http://github.com/urso/AwesomePrelude
[3] http://tom.lokhorst.eu/2009/09/deeply-embedded-dsls
[4] http://tom.lokhorst.eu/2010/02/awesomeprelude-presentation-video

On 28 Okt., 12:09, Dupont Corentin corentin.dup...@gmail.com wrote:
 Thank you for your rich responses.

 Indeed I think I miss some thinks in my DSL, that would make things easier
 to deal with lists and first class functions.
 I don't really know what for now.
 Perhaps a List Constructor? Or a constructor on functions like yours Ryan?
 EAp :: Exp ref (a - b) - Exp ref a - Exp ref b
 It's from which DSL? It is accessible on the net?

 Chris suggested me that I can only define the Foldr constructor and deduce
 Map from it.
 But maybe I have to add a List constructor for that.

 But in the suggestions from Ryan and Brandon I don't understand why I should
 add an extra type parameter and what it is!

 Steffen: Wow nice. I'll integrate that ;)

 I'm also looking at the Atom's DSL to get inspiration.
 Something I don't understand in it is that it has two languages, on typed:

 data E a where
   VRef    :: V a - E a
   Const   :: a - E a
   Cast    :: (NumE a, NumE b) = E a - E b
   Add     :: NumE a = E a - E a - E a
 etc.

 And, along with it, an untyped counterpart:

 -- | An untyped term.
 data UE
   = UVRef UV
   | UConst Const
   | UCast  Type UE
   | UAdd   UE UE
 etc.

 What that for? What's the use of having beautiful GADT if you have to
 maintain an untyped ADT aside??

 Corentin

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: Map constructor in a DSL

2010-10-26 Thread steffen
Hi,

I think you may want to over think your types again.
Especially your Evaluator-Monad, and maybe your Map constructor.

The Problem is, due to your use of Either and the need for evalObs to
finally transform from Obs [a] type to Evaluator [a] you will end
up in another Monad for Either:

instance Monad (Either Actions) where
  return = Right
  (Left x) = _ = Left x
  (Right a) = f = f a

Then one solution may be:

evalObs (Map f obs) = evalMap (f.Konst) (evalObs obs)

evalMap :: (a - Obs b) - Evaluator [a] - Evaluator [b]
evalMap f o = liftE (map evalObs) (liftE (map f) o) = \x -
 case x of
   Left actions - return $ Left actions
   Right evals  - sequence evals = return .
sequence
-- first sequence evals creates [Either Actions a]
-- second sequence create Either Actions [a]


After building up the Evaluator [a] construct inside your Evaluator-
Monad, you have to join the construct evals back into your real
Monad and since you pass around results using Either inside your
Evaluator-Monad, you have to treat the Either-type just like another
Monad.

If you get stuck on your types, define new toplevel functions (as
undefined) each taking one argument less  and play with the types in
your files and in ghci until it begins to make sense.



On 26 Okt., 19:42, Dupont Corentin corentin.dup...@gmail.com wrote:
 Hey Chris!
 Values for PlayerNumber are acquired at evaluation time, from the state of
 the system.

 I have not included the evaluation of AllPlayers.
 Here how it looks:

 evalObs AllPlayers  = return . pure  = gets players

 But when you build your Obs, you have yet no idea how much players it will
 be.
 This is just symbolic at this stage.

 To give you a better insight, here is want I want to do with Map:

 everybodyVote :: Obs [Bool]
 everybodyVote = Map (Vote (Konst Please vote)) AllPlayers

 In memory, everybodyVote is just a tree.
 This rule can be executed latter whenever I want to perform this democratic
 vote ;)

 Hope this answer to your question.
 Corentin

 On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
 chrisd...@googlemail.comwrote:







  On 26 October 2010 18:07, Dupont Corentin corentin.dup...@gmail.com
  wrote:
   But how can I write the evaluator for Map?

  Where do values for PlayerNumber come from? Unless I'm mistaken, the
  only thing that Map can be used with is Obs [PlayerNumber], a list of
  values PlayerNumber which we have no means of acquiring in order to
  provide to the Map function.



 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: Map constructor in a DSL

2010-10-26 Thread steffen
Ah, it's too early in the morning...
There is still some room to simplify (e.g. fuse the liftE (map ...)
ops).

Here a simpler Version:

evalObs (Map f obs) = liftE (map (evalObs.f.Konst)) (evalObs obs)
=
either (return.Left)
   (sequence = return . sequence)


On 27 Okt., 06:12, steffen steffen.sier...@googlemail.com wrote:
 Hi,

 I think you may want to over think your types again.
 Especially your Evaluator-Monad, and maybe your Map constructor.

 The Problem is, due to your use of Either and the need for evalObs to
 finally transform from Obs [a] type to Evaluator [a] you will end
 up in another Monad for Either:

     instance Monad (Either Actions) where
       return = Right
       (Left x) = _ = Left x
       (Right a) = f = f a

 Then one solution may be:

     evalObs (Map f obs) = evalMap (f.Konst) (evalObs obs)

     evalMap :: (a - Obs b) - Evaluator [a] - Evaluator [b]
     evalMap f o = liftE (map evalObs) (liftE (map f) o) = \x -
                  case x of
                    Left actions - return $ Left actions
                    Right evals  - sequence evals = return .
 sequence
     -- first sequence evals creates [Either Actions a]
     -- second sequence create Either Actions [a]

 After building up the Evaluator [a] construct inside your Evaluator-
 Monad, you have to join the construct evals back into your real
 Monad and since you pass around results using Either inside your
 Evaluator-Monad, you have to treat the Either-type just like another
 Monad.

 If you get stuck on your types, define new toplevel functions (as
 undefined) each taking one argument less  and play with the types in
 your files and in ghci until it begins to make sense.

 On 26 Okt., 19:42, Dupont Corentin corentin.dup...@gmail.com wrote:







  Hey Chris!
  Values for PlayerNumber are acquired at evaluation time, from the state of
  the system.

  I have not included the evaluation of AllPlayers.
  Here how it looks:

  evalObs AllPlayers  = return . pure  = gets players

  But when you build your Obs, you have yet no idea how much players it will
  be.
  This is just symbolic at this stage.

  To give you a better insight, here is want I want to do with Map:

  everybodyVote :: Obs [Bool]
  everybodyVote = Map (Vote (Konst Please vote)) AllPlayers

  In memory, everybodyVote is just a tree.
  This rule can be executed latter whenever I want to perform this democratic
  vote ;)

  Hope this answer to your question.
  Corentin

  On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
  chrisd...@googlemail.comwrote:

   On 26 October 2010 18:07, Dupont Corentin corentin.dup...@gmail.com
   wrote:
But how can I write the evaluator for Map?

   Where do values for PlayerNumber come from? Unless I'm mistaken, the
   only thing that Map can be used with is Obs [PlayerNumber], a list of
   values PlayerNumber which we have no means of acquiring in order to
   provide to the Map function.

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

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: dph question

2010-10-15 Thread steffen
 I trying to learn a bit about data parallel haskell, and started from the
 wiki page here:http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell.
 Two questions:

 The examples express the dot product as:

 dotp_double xs ys = sumP [:x *
 http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.
 y | x - xs | y - ys:]

 Unless I'm missing something, shouldn't this actually be:

 dotp_double xs ys = sumP [:x *
 http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.
 y | x - xs, y - ys:]

No, array comprehension desugaring works the same way as for list
comprehension.
So this correct:

dotp_double xs ys = sumP [:x * y | x - xs | y - ys:]

After desugaring this will be translated into (simplified):

dotp_double xs ys = sumP (zipWithP (*) xs ys)

which will multiply the arrays element wise and sum the result.

The other definition

dotp_double xs ys = sumP [:x * y | x - xs, y - ys:]

will be translated into (something equivalent):

dotp_double xs ys = sumP (concatMapP (\x - mapP (\y - x * y)) xs
ys)

which definitely is not the dot product.

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


Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Steffen Schuldenzucker

I don't know too much about GADTs, but it works fine with fundeps:

http://hpaste.org/40535/finite_list_with_fundeps

(This is rather a draft. If anyone can help me out with the TODOs, I'd be 
happy.)

-- Steffen


On 10/13/2010 10:40 AM, Eugene Kirpichov wrote:
 Well, in my implementation it's indeed impossible. It might be
 possible in another one. That is the question :)
 Perhaps we'll have to change the type of cons, or something.
 
 13 октября 2010 г. 12:37 пользователь Miguel Mitrofanov
 miguelim...@yandex.ru написал:
  So... you want your ones not to typecheck? Guess that's impossible, since
 it's nothing but fix application...

 13.10.2010 12:33, Eugene Kirpichov пишет:

 Well, it's easy to make it so that lists are either finite or bottom,
 but it's not so easy to make infinite lists fail to typecheck...
 That's what I'm wondering about.

 2010/10/13 Miguel Mitrofanovmiguelim...@yandex.ru:

  hdList :: List a n -  Maybe a
 hdList Nil = Nothing
 hdList (Cons a _) = Just a

 hd :: FiniteList a -  Maybe a
 hd (FL as) = hdList as

 *Finite  hd ones

 this hangs, so, my guess is that ones = _|_


 13.10.2010 12:13, Eugene Kirpichov пишет:

 {-# LANGUAGE ExistentialQuantification, GADTs, EmptyDataDecls #-}
 module Finite where

 data Zero
 data Succ a

 class Finite a where

 instance Finite Zero
 instance (Finite a) =Finite (Succ a)

 data List a n where
   Nil :: List a Zero
   Cons :: (Finite n) =a -List a n -List a (Succ n)

 data FiniteList a where
   FL :: (Finite n) =List a n -FiniteList a

 nil :: FiniteList a
 nil = FL Nil

 cons :: a -FiniteList a -FiniteList a
 cons a (FL x) = FL (Cons a x)

 list123 = cons 1 (cons 2 (cons 3 nil))

 ones = cons 1 ones -- typechecks ok

 ___
 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] Finite but not fixed length...

2010-10-13 Thread Steffen Schuldenzucker

Hmm, ok, I simplified the idea[1] and it looks like I'm getting the same
problem as you when trying to drop the 'n' parameter carrying the length of
the list.

Sad thing.

[1] http://hpaste.org/40538/finite_list__not_as_easy_as_i

On 10/13/2010 10:43 AM, Steffen Schuldenzucker wrote:
 
 I don't know too much about GADTs, but it works fine with fundeps:
 
 http://hpaste.org/40535/finite_list_with_fundeps
 
 (This is rather a draft. If anyone can help me out with the TODOs, I'd be 
 happy.)
 
 -- Steffen
 
 
 On 10/13/2010 10:40 AM, Eugene Kirpichov wrote:
 Well, in my implementation it's indeed impossible. It might be
 possible in another one. That is the question :)
 Perhaps we'll have to change the type of cons, or something.

 13 октября 2010 г. 12:37 пользователь Miguel Mitrofanov
 miguelim...@yandex.ru написал:
  So... you want your ones not to typecheck? Guess that's impossible, since
 it's nothing but fix application...

 13.10.2010 12:33, Eugene Kirpichov пишет:

 Well, it's easy to make it so that lists are either finite or bottom,
 but it's not so easy to make infinite lists fail to typecheck...
 That's what I'm wondering about.

 2010/10/13 Miguel Mitrofanovmiguelim...@yandex.ru:

  hdList :: List a n -  Maybe a
 hdList Nil = Nothing
 hdList (Cons a _) = Just a

 hd :: FiniteList a -  Maybe a
 hd (FL as) = hdList as

 *Finite  hd ones

 this hangs, so, my guess is that ones = _|_


 13.10.2010 12:13, Eugene Kirpichov пишет:

 {-# LANGUAGE ExistentialQuantification, GADTs, EmptyDataDecls #-}
 module Finite where

 data Zero
 data Succ a

 class Finite a where

 instance Finite Zero
 instance (Finite a) =Finite (Succ a)

 data List a n where
   Nil :: List a Zero
   Cons :: (Finite n) =a -List a n -List a (Succ n)

 data FiniteList a where
   FL :: (Finite n) =List a n -FiniteList a

 nil :: FiniteList a
 nil = FL Nil

 cons :: a -FiniteList a -FiniteList a
 cons a (FL x) = FL (Cons a x)

 list123 = cons 1 (cons 2 (cons 3 nil))

 ones = cons 1 ones -- typechecks ok

 ___
 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


[Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread steffen
  A slightly different suggestion from Simon PJ and myself (we agreed on
  something syntax-related :-) is the following:

   \case 1 - f
         2 - g
  ...
   \case { 1 - f; 2 - g }

 +1

 I like this because it has exactly the same properties of Max's
 case-of, but is shorter and still reads with sense.
+1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: EDSL for Makefile

2010-10-06 Thread steffen
The Reader monad just establishes an environment, so you can use ask
to retrieve a value from the environment.
Let's say you have the following types representing you Make-
Environment:

data MakeInfo = MakeInfo
{ target_  :: String
, sources_ :: [String]
}

then inside your Monad you can access MakeInfo using ask. Because
you may want to have IO available, let's use the Monad Transformer
version of the Reader Monad, to define our MakeMonad:

type MakeMonad = ReaderT MakeInfo IO

runMake :: MakeMonad () - MakeInfo - IO ()
runMake m makeInfo = runReaderT m makeInfo

and runMake will run it.

Then you can access source and target e.g. with Applicatives:

test = do
sources - sources_ $ ask
target  - target_ $ ask
system $ gcc -o  ++ target ++   ++ (foldl (++) $ map ('
':) sources)

Since using sources_ $ ask and such may still be annoying, this
gist[1] uses some (questionable) TypeClass-hackery and some extension
to overcome this problem...

Using this solution one can simply write:

test = sh $ gcc -o  target  sources

which looks somewhat nicer. This example also defines runTest and a
test function (which calls the shell command echo to print some
lines) you can try in ghci by typing runTest test...

[1] http://gist.github.com/614246

On 3 Okt., 16:56, C K Kashyap ckkash...@gmail.com wrote:
 On Sun, Oct 3, 2010 at 5:22 PM, steffen steffen.sier...@googlemail.com 
 wrote:
  If you don't want to mention r1 explicitly, but want to refer to
  target, sources and such only a monadic approach (e.g. Reader
  Monad) might be what you want.

 Thanks Steffen ... would you be able to give me an example?

 --
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: Lazy evaluation from Why Functional programming matters

2010-10-05 Thread steffen
Don't be to disappointed. One can always kinda fake lazy evaluation
using mutable cells.
But not that elegantly. In the example given above, all being used is
iterators as streams... this can also be expressed using lazy lists,
true. But one big difference between e.g. lazy lists and iterators is,
that lazy values are (operationally) replaced by their result wheres
values generated from iterators and streams are not.

For example one can use Iterators and chain them together in Java, to
achieve more or less the same space and runtime-efficiency found by
Stream-fusion in haskell (the Java JIT can abstract loads away, once
the iterators are build together). But If you need to access the
iterator's values more then once, you have to either force the full
iterator into a list or rerun/reevaluate the iterator every time you
need a value.

Lazy lists are nice, but haskell's laziness is not about lazy lists
only. For example lazy evaluation also matters when  creating
elegant Embedded DSLs... have you ever tried to build a more complex
EDSL without laziness and macros?

On 5 Okt., 16:52, C K Kashyap ckkash...@gmail.com wrote:
  Yes. It would slightly easier in, say,  C# or C++.
  I think 'D' achieves its implementation of the 'lazy' keyword using a
  similar approach.
  But I did not understand why you are disappointed ?

 The disappointment was not on a serious note ... the thing is, I
 constantly run into discussions
 about why fp with my colleagues - in a few of such discussions, I
 had mentioned that Haskell is the
 only well known language with lazy evaluation (IIRC, I read it
 somewhere or heard it in one of the videos)

 And I had built up this impression that laziness distinguished Haskell
 by a huge margin ... but it seems that is not the case.
 Hence the disappointment.

 --
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: EDSL for Makefile

2010-10-04 Thread steffen
Telling from the video and the slide, Neil's make system is actually
really cool. Indeed something I would really enjoy to use. It support
dynamic and static dependency tracking (more or less) out of the box
(by storing dependencies in a database file).
So you use want and need to tell the system about the static and
dynamic dependencies.
The want at the beginning just tells which targets to start.
Since you may want to choose your task via command line, you actually
would want to do something like:

main = do
wantDefault file1 = getArgs
file1 * ...

wantDefault default [] = want [default]
wantDefault _ args = want args

Since using String everywhere for dependencies can lead to errors, it
is always a good idea to replace the strings by constants you can
reuse.

Shake is more kind of a library. If you want a more make-like System
you can even write a preprocessor (like the haskell sinatra clone
bird), which even looks for your target symbols and then generates a
haskell file with target symbols replaced by Strings.

I hope the space leaks will be fixed in the future, so one can even
write long running processes which automatically detect changes and
rerun without user interaction and much more.

I actually wonder about the semantic differences between want and
need. Is need used to tell about dynamic dependencies and want for
static dependencies?

On 4 Okt., 05:41, C K Kashyap ckkash...@gmail.com wrote:
  mention_only_once file action = do
    want [file]
    file * action

  main = mention_only_once file1 $ \x - do need [file2]
                                             putStrLn Hello
                                             putStrLn World

 Thanks Bulat 
 I guess even this should work -

 main = do
   let file1=file1
   want [file1]
   file1 * \x - do
     need [file2]
     putStrLn Hello
     putStrLn World

 --
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] Re: EDSL for Makefile

2010-10-03 Thread steffen
If you don't want to mention r1 explicitly, but want to refer to
target, sources and such only a monadic approach (e.g. Reader
Monad) might be what you want.

On Oct 3, 6:14 am, C K Kashyap ckkash...@gmail.com wrote:
  Thanks Emil ... yeah, that works...I was wondering what I could do to
  not have to mention r1 explicitly.
  I'll check out Neil's pdf and video now - perhaps I'll find answers there.

 I checked out the video - nice - but I think, understandably, since
 its not open source yet, not much of implementations details were
 mentioned.

 So, I have this unanswered question nagging in my head. In the
 example below, how can I let the makefile writer refer to the target
 name and dependencies. Likr Emil mentioned, I could use target r1
 but I want to avoid having to mention r1.

 http://hpaste.org/40233/haskell_makefile_edsl

 --
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[Haskell-cafe] targeting Haskell compiler to embedded/hardware

2010-09-29 Thread -Steffen

If you are really interested in embedded realtime code you may want to have a
look at the timber language[1] or bit-c[2]. Another very interesting project
is this[3] developing a new Haskell like language called Habit for systems
programming.

There are also some great papers about systems programming and problems in
Haskell. For example Strongly typed memory areas programming systems-level
data structures in a functional language.

[1] http://www.timber-lang.org/
[2] http://www.bitc-lang.org/
[3] http://hasp.cs.pdx.edu/
[4] http://web.cecs.pdx.edu/~mpj/pubs/bytedata.pdf




Tom Hawkins-2 wrote:
 
 A few years ago I attempted to build a Haskell hardware compiler
 (Haskell - Verilog) based on the Yhc frontent.  At the time I was
 trying to overcome several problems [1] with implementing a hardware
 description language as a light eDSL, which convinced me a proper
 compiler may be a better approach.  Yhc was recommended as a good
 starting point since it had a simpler IR compared with GHC -- at least
 at the time.
 
 I am considering restarting this effort, but this time to target hard
 realtime embedded code.  What is the recommended compiler to start
 from?  I need an IR that is post type checking with as much desugaring
 as possible, and a code base that is relatively easy to splice and
 build.
 
 My other requirement is not to be bound to IO () for 'main'.  The top
 level will be a monad, but with different semantics than IO.  I would
 also like to reuse the standard library, with exception to the values
 related to IO.
 
 What are my options?
 
 Thanks.
 
 -Tom
 
 [1] Lack of observable sharing; function definitions, case
 expressions, ADTs disappear at compile time; etc.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://old.nabble.com/Retargeting-Haskell-compiler-to-embedded-hardware-tp29834645p29836816.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: re[Haskell-cafe] cord update

2010-09-14 Thread -Steffen

While we are at it using Semantic Editor Combinators (sec on hackage):

 {-# LANGUAGE TemplateHaskell #-}

 module T where

 import Data.SemanticEditors

 data MyRecord = MyRecord { field1 :: String, field2 :: Int, field3 :: Bool
 }
   deriving(Show)

 mkEditors [''MyRecord]

 editRecord str =
 (editField1.set) newName -- set field1 to new value
   . editField3 not  -- apply function (not) to field3
   . (editIf field3.editField2.editIf (10)) (1+)
  -- increase field2's value if field2's value  10
  -- and field3 is True

sec also supports functions, lists, Maybe and other monads


Chris Eidhof wrote:
 
 For completeness, using fclabels (yet another record package) you can
 write it like this:
 
 
 {-# LANGUAGE TemplateHaskell #-}
 module Records where
 
 import Data.Record.Label
 
 data MyRecord = MyRecord { _field1 :: String, _field2 :: Int, _field3 ::
 Bool }
 
 $(mkLabels [''MyRecord])
 
 modifyThree f g h = modL field1 f
   . modL field2 g
   . modL field3 h
 
 -chris
 
 On 11 sep 2010, at 19:21, Jonathan Geddes wrote:
 
 I know that record updates is a topic that has become a bit of a dead
 horse, but here I go anyway:
 
 I find that most of the record updates I read and write take the form
 
 someUpdate :: MyRecord - MyRecord
 someUpdate myRecord = myRecord
{ field1 = f $ field1 myRecord
, field2 = g $ field2 myRecord
, field3 = h $ filed3 myRecord
}
 
 I find myself wishing I could write something more like
 
 someUpdate :: MyRecord - MyRecord
 someUpdate myRecord = myRecord
{ field1 = f
, field2 = g
, field3 = h
}
 
 with equivalent semantics. Here = reads is transformed by. Operator
 = could still be used for assignment as in current record updates.
 
 The best part about such an extension, in my opinion, is that it would
 open the door for anonymous lambda record updates. Something like:
 
 someUpdate :: MyRecord - MyRecord
 someUpdate = \{field1 = f, field2 = g, field3 = h}
 
 again, with the same semantics. This becomes possible because you no
 longer need to refer to the record within the {} part of the update.
 
 This would be useful, for example, in the State monad. We could write:
 
 someStateTransform :: State MyRecord ()
 someStateTransform = do
modify $ \{field1 = (++!)}
...
 
 where currently we see code like
 
 someStateTransform :: State MyRecord ()
 someStateTransform = do
modify $ \record-record{field1 = (++!) $ field1 record}
...
 
 which repeats the record name 3 times and the field name twice. The
 repetition just feels out of place next to all the other terse,
 readable Haskell code in the program.
 
 So what do my fellow haskellers think? Is this idea worth writing up a
 proposal for?
 
 Alternatively, can you offer me some advice on writing code in Haskell
 2010 that avoids the ugly, repetitive style of record update?
 
 --Jonathan
 ___
 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
 
 

-- 
View this message in context: 
http://old.nabble.com/record-update-tp29686064p29710821.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] in-equality type constraint?

2010-07-17 Thread Steffen Schuldenzucker
On 07/17/2010 03:50 AM, Gábor Lehel wrote:
 Does TypeEq a c HFalse imply proof of inequality, or unprovability
 of equality?

Shouldn't these two be equivalent for types?

 
 On Sat, Jul 17, 2010 at 2:32 AM, Steffen Schuldenzucker
 sschuldenzuc...@uni-bonn.de wrote:
 On 07/17/2010 01:08 AM, Paul L wrote:
 Does anybody know why the type families only supports equality test
 like a ~ b, but not its negation?


 This has annoyed me, too. However, HList provides something quite similar,
 namely the TypeEq[1] fundep-ed class which will answer type-equality with a
 type-level boolean. (this is actually more powerful than a simple constraint,
 because it allows us to introduce type-level conditionals)

 To turn it into a predicate, you can use something like

 (disclaimer: untested)

 class C a b c where  -- ...

 -- for some reason, we can provide an instance C a b [c] *except* for
 -- a ~ c.
 instance (TypeEq a c x, x ~ HFalse) = a b [c] where  -- ...

 Best regards,

 Steffen

 [1]
 http://hackage.haskell.org/packages/archive/HList/0.2.3/doc/html/Data-HList-FakePrelude.html#t%3ATypeEq
 (Note that for it to work over all types, you have to import one of the
 Data.HList.TypeEqGeneric{1,2} modules)
 ___
 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] in-equality type constraint?

2010-07-16 Thread Steffen Schuldenzucker
On 07/17/2010 01:08 AM, Paul L wrote:
 Does anybody know why the type families only supports equality test
 like a ~ b, but not its negation?
 

This has annoyed me, too. However, HList provides something quite similar,
namely the TypeEq[1] fundep-ed class which will answer type-equality with a
type-level boolean. (this is actually more powerful than a simple constraint,
because it allows us to introduce type-level conditionals)

To turn it into a predicate, you can use something like

(disclaimer: untested)

 class C a b c where  -- ...

 -- for some reason, we can provide an instance C a b [c] *except* for
 -- a ~ c.
 instance (TypeEq a c x, x ~ HFalse) = a b [c] where  -- ...

Best regards,

Steffen

[1]
http://hackage.haskell.org/packages/archive/HList/0.2.3/doc/html/Data-HList-FakePrelude.html#t%3ATypeEq
(Note that for it to work over all types, you have to import one of the
Data.HList.TypeEqGeneric{1,2} modules)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-07 Thread Steffen Schuldenzucker

Hum. You are right and I'm probably asking the wrong questions.

My original question was when it was possible to eliminate stack frames. For
example, in the 'f' function from my first post, we know that none of the
variables x and y will be needed after the recursive call to f, so we can just
re-use the current stack frame for it, preventing f from using additional
space for the recursion.

However, stack frames are an implementation detail and I thought
constant-space was an abstraction of my idea. Looks like it was not.

On 07/06/2010 04:07 PM, Lennart Augustsson wrote:
 Are you limiting your data structures to numbers?  In that case, only
 numbers of limited size, the answer is, of course, yes.  You can
 implement any such function in constant space and time. Just make a
 lookup table.
 
 Sent from my iPad
 
 On Jul 6, 2010, at 6:37, Steffen Schuldenzucker
 sschuldenzuc...@uni-bonn.de mailto:sschuldenzuc...@uni-bonn.de wrote:
 

 Forwarding this message to the list.

 No, I didn't think about the size of integers. For now, let all
 numbers have some bounded size.

  Original Message 
 Subject: Re: [Haskell-cafe] Criteria for determining if a recursive
 function can be implemented in constant memory
 Date:Tue, 6 Jul 2010 13:25:57 +1200
 From:Richard O'Keefe o...@cs.otago.ac.nz 
 mailto:o...@cs.otago.ac.nz
 To:  Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de
 mailto:sschuldenzuc...@uni-bonn.de



 On Jul 6, 2010, at 12:23 AM, Steffen Schuldenzucker wrote:
  Given the definition of a recursive function f in, say, haskell,  
  determine if f can be implemented in O(1) memory.

 How are you supposed to handle integer arithmetic?

 If you don't take the size of integers into account,
 then since a Turing machine can do any computation,
 it can run a Haskell interpreter, and since a Turing
 machine's tape can be modelled by a single integer
 (or more conveniently by two), any Haskell function
 can be implemented in O(1) Integers.

 If you do take the size of integers into account,
 then
 pow2 n = loop n 1
   where loop 0 a = a
 loop (m+1) a = loop m (a+a)
 requires O(n) memory.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org mailto: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


Fwd: Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-06 Thread Steffen Schuldenzucker


Forwarding this message to the list.

No, I didn't think about the size of integers. For now, let all numbers 
have some bounded size.


 Original Message 
Subject: 	Re: [Haskell-cafe] Criteria for determining if a recursive 
function can be implemented in constant memory

Date:   Tue, 6 Jul 2010 13:25:57 +1200
From:   Richard O'Keefe o...@cs.otago.ac.nz
To: Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de



On Jul 6, 2010, at 12:23 AM, Steffen Schuldenzucker wrote:

 Given the definition of a recursive function f in, say, haskell,
 determine if f can be implemented in O(1) memory.


How are you supposed to handle integer arithmetic?

If you don't take the size of integers into account,
then since a Turing machine can do any computation,
it can run a Haskell interpreter, and since a Turing
machine's tape can be modelled by a single integer
(or more conveniently by two), any Haskell function
can be implemented in O(1) Integers.

If you do take the size of integers into account,
then
pow2 n = loop n 1
  where loop 0 a = a
loop (m+1) a = loop m (a+a)
requires O(n) memory.

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


Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-06 Thread Steffen Schuldenzucker

On 7/5/2010 8:33 PM, Andrew Coppin wrote:

Tillmann Rendel wrote:

Hi Steffen,

Steffen Schuldenzucker wrote:
Given the definition of a recursive function f in, say, haskell, 
determine if f can be implemented in O(1) memory.


Constant functions are implementable in O(1) memory, but interpreters 
for turing-complete languages are not, so the property of being 
implementable in O(1) memory is non-trivial and therefore, by Rice's 
theorem, undecidable.


Damn Rice's theorum, spoiling everybody's fun all the time... ;-)


Definitely! Thanks, Tillmann, for this quite clear answer.

Of course, as I understand it, all the theorum says is that no single 
algorithm can give you a yes/no answer for *every* possible case. So 
the next question is is it decidable in any 'interesting' cases?


Then of course you have to go define 'interesting'...


Yes, perhaps I should reformulate my original question to something like

What is a good algorithm for transforming an algorithm written in a 
functional language to constant-memory imperative code? Which properties 
must the functional version satisfy?


(one answer would be tail-call optimization, but, as I pointed out in my 
first post, I guess this isn't the whole story)


or even:

Can you tell me an example of a set of functionally-defined algorithms 
maximal in the property that there exists a single algorithm which 
transforms them all into constant-memory imperative code?


-- Steffen

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


[Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-05 Thread Steffen Schuldenzucker


Dear Cafe,

since a little discussion with my tutor I am wondering how the following 
problem can be solved and if it is decidable:


Given the definition of a recursive function f in, say, haskell, 
determine if f can be implemented in O(1) memory.


First I thought the solution would be check if f is tail-recursive. 
However, consider the following definition:


 -- for the sake of uniformity
 if' c t e = if c then t else e

 f :: (Num a) = a - a - a
 f x y = if' (x = 0) y $
if' (x = 2) (f (x-2) (y+1)) (f (x-1) y)

(I don't really care what this function computes as long as it 
terminates, which is obvious)


Although ghc will probably not perform this optimization, f can be 
realized in O(1) mem:


// trying to duplicate f's structure as closely as possible
double f( double x, double y )
{
START:
if ( x = 0 )
return y;
else
{
if ( x = 2 )
{
x = x - 2;
y = y + 1;
goto START;
}
else
{
x = x - 1;
y = y;
goto START;
}
}
}

It is crucial that (the second) if' does not use both of its last two 
arguments, but only one. If we replace the second if' by, say


 g :: (Num a) = c - a - a - a
 g c t e = if' c (t + e) (t - e)

, then we have to compute *both* (f (x-2) (y+1)) and (f (x-1) y), and x 
and y have to be kept in memory during the call to (f (x-2) (y+1)), 
therefore f cannot be implemented in constant memory. (read: I haven't 
found a way which does not radically alter f's structure).


So, does someone know how to solve this or can prove that it can't be 
solved?


Best regards,

Steffen

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


Re: [Haskell-cafe] More experiments with ATs

2010-07-04 Thread Steffen Schuldenzucker
On 07/04/2010 01:49 PM, Sjoerd Visscher wrote:
 
 On Jul 4, 2010, at 11:31 AM, Andrew Coppin wrote:
  
 type family F f a :: *
 class RFunctor f where
  (%) :: f a b - (a - b) - F f a - F f b


 I have literally no idea what a type family is. I understand ATs (I think!), 
 but TFs make no sense to me.

 (For this reason, most if not all of the rest of this post doesn't make 
 sense.)
 
 I would have liked to use ATs here, like this:
 
 class RFunctor f where
   type F f a :: *
   (%) :: f a b - (a - b) - F f a - F f b
 
 But this isn't valid as ATs require all type variables to be in scope, and 
 'a' isn't. 
 There's a GHC ticket for this: http://hackage.haskell.org/trac/ghc/ticket/3714

This works (on my ghc-6.12.2):

 class Rfunctor f where
 type F f :: * - *
 (%) :: f a b - (a - b) - F f a - F f b

 [...]

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


Re: [Haskell-cafe] How to build an Indicator Type for a type class?

2010-06-03 Thread Steffen Schuldenzucker
On 06/02/2010 03:59 AM, Brent Yorgey wrote:
 Perhaps something here may be of use?
 
   http://okmij.org/ftp/Haskell/types.html#class-based-overloading

Enlightening. Thanks a lot. For the curious, here is my solution:

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=25907#a25907

I'm gonna read the HList paper now...

Best regards,

Steffen

   http://okmij.org/ftp/Haskell/types.html#class-based-dispatch
 
 -Brent
 
 On Mon, May 31, 2010 at 01:32:18PM +0200, Steffen Schuldenzucker wrote:
 Dear Cafe,

 let:

 data True
 data False

 class C a

 (arbitrary instances for C may follow)

 Now, how to obtain an Indicator Type for C, i.e. a type IndC that is 
 defined
 via a type family / fundep / ... , so that

 IndC a = Trueforall a which are instances of C
 IndC a = False   for all other a.

 I've collected some failed approaches here[1]. My key problem is that if I
 define (in the 3rd try):

 instance (C a) = IndC3 a True

 , it does *not* mean Define this instance for all a which are an instance of
 C, but Define the instance IndC3 a True for all types a, but it's not gonna
 work if a is not an instance of C.

 Does anyone have another idea?

 Background:

 After having implemented type-level lists[2] and a quicksort on them[3], I'd
 like to have type-level sets. In their most simple implementation, sets are
 just (unsorted) lists like this:

 data Nil
 data Cons a b
 class Elem x l
 (instances for Elem so that Elem x l iff x is an element of the list l)

 Now I want:

 type family Insert x s :: *

 Insert x s = s   forall (x, s) with (Elem x s)
 Insert x s = Cons x sfor all other (x, s).


 Thanks a lot!

 Steffen


 [1] http://hpaste.org/fastcgi/hpaste.fcgi/view?id=25832#a25832
 [2] Kiselyov, Peyton-Jones, Shan: Fun with type functions

 http://research.microsoft.com/en-us/um/people/simonpj/papers/assoc-types/fun-with-type-funs/typefun.pdf
 [3] I rewrote this algorithm using type families instead of fundeps:

 http://www.haskell.org/haskellwiki/Type_arithmetic#An_Advanced_Example_:_Type-Level_Quicksort
 ___
 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


[Haskell-cafe] How to build an Indicator Type for a type class?

2010-06-01 Thread Steffen Schuldenzucker
Dear Cafe,

let:

 data True
 data False

 class C a

(arbitrary instances for C may follow)

Now, how to obtain an Indicator Type for C, i.e. a type IndC that is defined
via a type family / fundep / ... , so that

IndC a = True   forall a which are instances of C
IndC a = False  for all other a.

I've collected some failed approaches here[1]. My key problem is that if I
define (in the 3rd try):

 instance (C a) = IndC3 a True

, it does *not* mean Define this instance for all a which are an instance of
C, but Define the instance IndC3 a True for all types a, but it's not gonna
work if a is not an instance of C.

Does anyone have another idea?

Background:

After having implemented type-level lists[2] and a quicksort on them[3], I'd
like to have type-level sets. In their most simple implementation, sets are
just (unsorted) lists like this:

 data Nil
 data Cons a b
 class Elem x l
(instances for Elem so that Elem x l iff x is an element of the list l)

Now I want:

 type family Insert x s :: *

Insert x s = s  forall (x, s) with (Elem x s)
Insert x s = Cons x s   for all other (x, s).


Thanks a lot!

Steffen


[1] http://hpaste.org/fastcgi/hpaste.fcgi/view?id=25832#a25832
[2] Kiselyov, Peyton-Jones, Shan: Fun with type functions

http://research.microsoft.com/en-us/um/people/simonpj/papers/assoc-types/fun-with-type-funs/typefun.pdf
[3] I rewrote this algorithm using type families instead of fundeps:

http://www.haskell.org/haskellwiki/Type_arithmetic#An_Advanced_Example_:_Type-Level_Quicksort
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data creation pattern?

2010-05-13 Thread Steffen Schuldenzucker

Hi.

Stephen Tetley wrote:

Hi Eugene

Is something like this close to what you want:

For example this builds an object with ordered strings...

makeOrdered :: String - String - String - Object
makeOrdered a b c = let (s,t,u) = sort3 (a,b,c) in Object s t u
  

Or just:

makeOrdered a b c = let (s:t:u:_) = sort [a, b, c] in Object s t u

(no support code required)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ada-style ranges

2010-04-26 Thread Steffen Schuldenzucker
On 04/26/2010 12:50 PM, hask...@kudling.de wrote:
 
 
 Hi list,
 
  
 
 how would you describe Ada's ranges in Haskell's typesystem?
 
 http://en.wikibooks.org/wiki/Ada_Programming/Types/range

Hi Lenny,

can non-constant expressions be given as arguments to 'range'? If not, then
what about a opaque wrapper type?

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Range1 (Range1, fromRange1, mkBounded, mkRange1) where

newtype Range1 = Range1 { fromRange1 :: Integer }
deriving (Eq, Num, Ord, Show)

instance Bounded Range1 where
minBound = Range1 $ -5
maxBound = Range1 $ 10

mkBounded :: (Bounded a, Ord a) = (b - a) - b - Maybe a
mkBounded f x = case f x of
y | minBound = y  y = maxBound - Just y
  | otherwise  - Nothing

mkRange1 ::  Integer - Maybe Range1
mkRange1 = mkBounded Range1

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-08 Thread Steffen Schuldenzucker
On 03/08/2010 10:45 PM, Wolfgang Jeltsch wrote:
 The point is, of course, that such conversions are not only possible for 
 binary operations but for arbitrary values and that these conversions are 
 done 
 by a single generic function conv. I don’t think it would be possible to 
 implement conv without generalized newtype deriving.
 
 Any thoughts?
 

Hi Wolfgang,

it's not exactly the same, but...

 import Control.Applicative

 newtype Wrapped a = Wrap a deriving Show

 instance Functor Wrapped where
 fmap f (Wrap x) = Wrap $ f x

 instance Applicative Wrapped where
 pure = Wrap
 (Wrap f) * (Wrap x) = Wrap $ f x

 convBinOp :: (a - a - a) - (Wrapped a - Wrapped a - Wrapped a)
 convBinOp op x y = pure op * x * y

Best regards,

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


Re: [Haskell-cafe] classes with types which are wrapped in

2010-01-22 Thread Steffen Schuldenzucker

Hi Andrew,

Andrew U. Frank wrote:
here a simplistic case (i know that A could be reduced to [], my real cases 
are more complicated).


data A b = A b [b]

data Asup x ab y = Asup x ab y

class X a b where
push :: b - a b - a b

instance X A Int where
push b' (A b bs) = A b' (b:bs)

instance X Asup Char Int Float where
push b' (Asup a b c) = Asup a (push b' b) c

  
If I understand you correctly, what you want here are type level 
lambdas. Abusing notation:


instance X (\t - Asup Char t Float) Int where
   push b' (Asup a b c) = Asup a (push b' b) c

However, type level lambdas introduce lots of ambiguities and are 
therefore AFAIK not supported in haskell[1].



if i try with a type

type A_2 b = Asup Char (A b) Float

instance X A_2 Int where
push b' (Asup a b c) = Asup a (push b' b) c

(and --TypeSynonymInstances) i get:

Type synonym `A_2' should have 1 argument, but has been given 0
In the instance declaration for `X A_2 Int'
  
However, this error message looks strange. I tried to reduce this to a 
simpler case[1] and got the same message.
Does anyone know why it complains just about the number of type 
arguments (which is correct) ?


-- Steffen

[1] http://www.mail-archive.com/haskell-cafe@haskell.org/msg69579.html
[2] http://ideone.com/9BAj7MG7
(note that ideone is using ghc-6.8)

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


Re: [Haskell-cafe] lawless instances of Functor

2010-01-05 Thread Steffen Schuldenzucker
Brent Yorgey wrote:
 On Mon, Jan 04, 2010 at 11:49:33PM +0100, Steffen Schuldenzucker wrote:
 [...]
 
 As others have pointed out, this doesn't typecheck; but what it DOES
 show is that if we had a type class
 
   class Endofunctor a where
 efmap :: (a - a) - f a - f a
 
 then it would be possible to write an instance for which efmap id = id
 but efmap (f . g) /= efmap f . efmap g.  The difference is that with
 the normal Functor class, once you have applied your function f :: a
 - b to get a b, you can't do anything else with it, since you don't
 know what b is.  With the Endofunctor class, once you have applied f
 :: a - a, you CAN do something with the result: namely, apply f
 again.  

Oops. Yeah, sorry, it's been ... late and stuff...

Steffen

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


Re: [Haskell-cafe] lawless instances of Functor

2010-01-04 Thread Steffen Schuldenzucker
Hi Paul,

Paul Brauner wrote:
 Hi,

 I'm trying to get a deep feeling of Functors (and then pointed Functors,
 Applicative Functors, etc.). To this end, I try to find lawless
 instances of Functor that satisfy one law but not the other.

 I've found one instance that satisfies fmap (f.g) = fmap f . fmap g
 but not fmap id = id:
 [...]
 But I can't come up with an example that satifies law 1 and not law 2.
 I'm beginning to think this isn't possible but I didn't read anything
 saying so, neither do I manage to prove it.

 I'm sure someone knows :)

data Foo a = Foo a

instance Functor Foo where
fmap f (Foo x) = Foo . f . f $ x

Then:

fmap id (Foo x) == Foo . id . id $ x == Foo x

fmap (f . g) (Foo x)  == Foo . f . g . f . g $ x
fmap f . fmap g $ (Foo x) == Foo . f . f . g . g $ x

Now consider Foo Int and

fmap ((+1) . (*3)) (Foo x)  == Foo $ (x * 3 + 1) * 3 + 1
== Foo $ x * 9 + 4
fmap (+1) . fmap (*3) $ (Foo x) == Foo $ x * 3 * 3 + 1 + 1
== Foo $ x * 9 + 2

-- Steffen


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


Re: [Haskell-cafe] Partially applied functions

2009-11-28 Thread Steffen Schuldenzucker
Ozgur Akgun wrote:
 Hi cafe,
 
 Is such a thing possible,
 
 
 add :: Int - Int - Int
 add x y = x + y
 
 -- a list of partially applied functions
 adds = [add 3, add 5, add 7, add 3, add 5, add 8]
 
 -- an example usage of the list
 k = map (\ f - f 10 ) adds
 
 add3s = filter (?) adds -- add3s = [add 3, add 3]
 addEvens = filter (?) adds --addEvens = [add 8]
 
 
 I want to have functions in place of the ? signs. I guess one would need
 a way of extracting the applied value from a partially applied function
 (or totally, doesn't matter)

Well, sure you can:

add3s = filter (\f - f 0 == 3) adds
addEvens = filter (\f - isEven $ f 0) adds

This is only possible since there is that special property of the
addition that (add a) 0 == a forall a, i.e. you can extract the first
parameter back out of the partial applied function by passing 0 as a
second parameter.

It clearly depends on the function how much information about the
parameters can be read from the result.


-- Steffen

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


Re: [Haskell-cafe] What does the `forall` mean ?

2009-11-12 Thread Steffen Schuldenzucker
Andrew Coppin wrote:
 
 I just meant it's not immediately clear how
 
  foo :: forall x. (x - x - y)
 
 is different from
 
 foo :: (forall x. x - x) - y

Uhm, I guess you meant

foo :: forall x. ((x - x) - y)

VS.

foo :: (forall x. x - x) - y


, didn't you?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   >