Re: [Haskell-cafe] Open Source project suitable for 2-3 persons this fall?

2013-07-05 Thread Tobias Dammers
There's one of my hobby projects that could use some manpower to
bootstrap it into a production-quality tool. It's an HTML templating
system; right now it reads input templates in one of two languages (one
very declarative, very similar to Python's jinja2, the other being a
locally-pure functional language with a curly-bracket syntax), and it
can output PHP and JavaScript as well as execute templates directly in
Haskell code. There's also a rather experimental JSON-based intermediate
format, designed for high-security scenarios (JSON can be parsed
quickly, but because it cannot contain arbitrary code, a compromised
compiler can be mitigated by whitelisting what the runtime can do; this
way, only the runtime has to be audited, not the compiler).

There is an incomplete implementation of a PHP library that can
interpret this intermediate JSON format, but it hasn't been used in any
production-quality project yet.

The core part is the compiler, consisting of a
Parsec-based parser, an AST, an optimizer, and a few backends.

The unique selling points:

* Pre-compile your templates - now you can have the cake (expressive
  clean template language) and eat it too (great performance, because
  it's pre-compiled to your web app's native language).
* Use the same template for PHP, Haskell and JavaScript (and maybe
  others, too).
* Bye bye XSS: HTML-encoding is the default.
* Extensible: Hook up your own native functions - it's as simple as
  adding a function to your template input data, then calling it inside
  the template.

It could use some work in a lot of areas; projects could include, for
example:

- Getting the JavaScript backend to support 100% of the language
  features (right now, only the direct-execution and PHP backends pass
  all tests)
- Implement some glue to allow easy embedding in Haskell web
  applications (yesod / happstack / snap)
- Add more features to the input language (some of which would also
  require some changes to the backends), e.g.:
  - range literals
  - list comprehensions
  - indexed for-each, or some way of getting the current iteration's
index; very useful for things like zebra-stripe data grids and
such
- Add other backends (Python and Ruby would be the most obvious
  candidates, but I'm really open to anything)
- Add more library functions
- A better optimizer
- Some tooling and integration support, e.g. some kind of mechanism to
  switch between executing on-the-fly (for development) and using
  pre-compiled templates (for production), something to implement
  graceful degrading on the client side (use client-side templates when
  possible, fall back to postbacks and server-side templates as needed),
  syntax highlighters for popular editors, etc.

Anyway, here's the source:

https://bitbucket.org/tdammers/hpaco

The PHP lib/script that can produce and run a subset of the JSON
intermediate format is here:

https://bitbucket.org/tdammers/phpaco

(Any contributions, feedback, etc., very welcome)

On Thu, Jul 04, 2013 at 05:26:59PM +0200, Anders Bech Mellson wrote:
 Is there any project that needs working this fall which could be used as a
 university project?
 
 I am in the university (M.Sc. in software development),
 so I am mainly looking for project ideas (preferably concrete ones).
 
 We are 2-3 students that have ~10 hours pr week for 3 months to work on a
 project.
 
 Is there a listing somewhere with project ideas for contributing to the
 Haskell community?
 
 Thanks in advance,
 Anders

 ___
 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] Open Source project suitable for 2-3 persons this fall?

2013-07-05 Thread Guillaume Hoffmann
Hi Anders,

the Darcs project has a few proposals that you can look at:
http://darcs.net/GSoC

The proposals were written for summer of code projects that involve
more time dedication, but they can be reshaped into smaller projects.
Feel free to mail me or to discuss it on the #darcs IRC channel on
irc.freenode.net.

Guillaume

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


[Haskell-cafe] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Nicholls, Mark
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 class Foo x y | x - y, y - x
 instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made Integer,Integer a member of it...

Something like that anyway

Then I go

 data Bar

 instance Foo Bar x

Error!but I'm think I understand thisI can't claim that Bar,x is a 
member of Foo and Integer,Integer is member of Foo and preserve my functional 
dependencies, because Bar,Integer is now a member of Foo..

Bad programmer...


So how I naively go


 class NotAnInteger a

 instance (NotAnInteger x) = Foo Bar x

I haven't declared integer to be NotAnIntegerso (in a closed 
world)this would seem to exclude the contradictionbut...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12

So

i)I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of Foo across different 
combinations of types, without them colliding.







CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK  Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Erik Hesselink
The constraint on an instance never influences which instance is
selected. So as far as instance selection goes, 'instance Foo x' and
'instance C x = Foo x' are the same. The constraint is only checked
after the instance is selected.

Erik

On Fri, Jul 5, 2013 at 2:43 PM, Nicholls, Mark nicholls.m...@vimn.com wrote:
 Hello,



 I largely don’t know what I’m doing or even trying to do, it is a voyage
 into the unknown….but….if I go…



 {-# LANGUAGE MultiParamTypeClasses #-}

 {-# LANGUAGE FunctionalDependencies #-}

 {-# LANGUAGE FlexibleInstances #-}

 {-# LANGUAGE UndecidableInstances #-}



 class Foo x y | x - y, y - x

 instance Foo Integer Integer



 That seems to work….and my head seems to say…your created some sort of
 binary relation between 2 types…and made Integer,Integer a member of it…



 Something like that anyway….



 Then I go….



 data Bar



 instance Foo Bar x



 Error!but I’m think I understand this….I can’t claim that Bar,x is a
 member of Foo and Integer,Integer is member of Foo and preserve my
 functional dependencies, because Bar,Integer is now a member of Foo..



 Bad programmer…….





 So how I naively go….





 class NotAnInteger a



 instance (NotAnInteger x) = Foo Bar x



 I haven’t declared integer to be “NotAnInteger”….so (in a closed
 world)….this would seem to exclude the contradiction….but…





 Functional dependencies conflict between instance declarations:

   instance Foo Integer Integer -- Defined at liam1.lhs:7:12

   instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12



 So

 i)I clearly don’t understand something about the type
 system.

 ii)   I don’t know how to restrict type variables in
 instance declarations….i.e. how do I use the notion of “Foo” across
 different combinations of types, without them colliding.

















 CONFIDENTIALITY NOTICE

 This e-mail (and any attached files) is confidential and protected by
 copyright (and other intellectual property rights). If you are not the
 intended recipient please e-mail the sender and then delete the email and
 any attached files immediately. Any further use or dissemination is
 prohibited.

 While MTV Networks Europe has taken steps to ensure that this email and any
 attachments are virus free, it is your responsibility to ensure that this
 message and any attachments are virus free and do not affect your systems /
 data.

 Communicating by email is not 100% secure and carries risks such as delay,
 data corruption, non-delivery, wrongful interception and unauthorised
 amendment. If you communicate with us by e-mail, you acknowledge and assume
 these risks, and you agree to take appropriate measures to minimise these
 risks when e-mailing us.

 MTV Networks International, MTV Networks UK  Ireland, Greenhouse,
 Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
 International, Be Viacom, Viacom International Media Networks and VIMN and
 Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
 Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks
 Europe Inc.  Address for service in Great Britain is 17-29 Hawley Crescent,
 London, NW1 8TT.


 ___
 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] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Tikhon Jelvis
You're running into the open worldassumption--anybody could come along
and make Integer part of your NotAnInteger class, and there's nothing you
can do to stop them. This is a design tradeoff for typeclasses: typeclass
instances are always global and are exported to all other modules you use.
This means you cannot ensure a type is *not* part of a typeclass. (Or, at
the very least, you can't convince GHC of this fact.)

For more information about this, take a look at the following StackOverflow
question:
http://stackoverflow.com/questions/8728596/explicitly-import-instances
On Jul 5, 2013 8:47 AM, Nicholls, Mark nicholls.m...@vimn.com wrote:

  Hello,

 ** **

 I largely don’t know what I’m doing or even trying to do, it is a voyage
 into the unknown….but….if I go…

 ** **

  {-# LANGUAGE MultiParamTypeClasses #-}

  {-# LANGUAGE FunctionalDependencies #-}

  {-# LANGUAGE FlexibleInstances #-}

  {-# LANGUAGE UndecidableInstances #-}

 ** **

  class Foo x y | x - y, y - x

  instance Foo Integer Integer

 ** **

 That seems to work….and my head seems to say…your created some sort of
 binary relation between 2 types…and made Integer,Integer a member of it…
 

 ** **

 Something like that anyway….

 ** **

 Then I go….

 ** **

  data Bar

 ** **

  instance Foo Bar x

 ** **

 Error!but I’m think I understand this….I can’t claim that Bar,x is a
 member of Foo and Integer,Integer is member of Foo and preserve my
 functional dependencies, because Bar,Integer is now a member of Foo..***
 *

 ** **

 Bad programmer…….

 ** **

 ** **

 So how I naively go….

 ** **

 ** **

  class NotAnInteger a

 ** **

  instance (NotAnInteger x) = Foo Bar x

 ** **

 I haven’t declared integer to be “NotAnInteger”….so (in a closed
 world)….this would seem to exclude the contradiction….but…

 ** **

 ** **

 Functional dependencies conflict between instance declarations:

   instance Foo Integer Integer -- Defined at liam1.lhs:7:12

   instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12**
 **

 ** **

 So 

 **i)**I clearly don’t understand something about the
 type system.

 **ii)   **I don’t know how to restrict type variables in
 instance declarations….i.e. how do I use the notion of “Foo” across
 different combinations of types, without them colliding.

 ** **

 ** **

 ** **

 ** **

 ** **

 ** **

 ** **



 CONFIDENTIALITY NOTICE

 This e-mail (and any attached files) is confidential and protected by
 copyright (and other intellectual property rights). If you are not the
 intended recipient please e-mail the sender and then delete the email and
 any attached files immediately. Any further use or dissemination is
 prohibited.

 While MTV Networks Europe has taken steps to ensure that this email and
 any attachments are virus free, it is your responsibility to ensure that
 this message and any attachments are virus free and do not affect your
 systems / data.

 Communicating by email is not 100% secure and carries risks such as delay,
 data corruption, non-delivery, wrongful interception and unauthorised
 amendment. If you communicate with us by e-mail, you acknowledge and assume
 these risks, and you agree to take appropriate measures to minimise these
 risks when e-mailing us.

 MTV Networks International, MTV Networks UK  Ireland, Greenhouse,
 Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
 International, Be Viacom, Viacom International Media Networks and VIMN and
 Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
 Europe is a partnership between MTV Networks Europe Inc. and Viacom
 Networks Europe Inc.  Address for service in Great Britain is 17-29 Hawley
 Crescent, London, NW1 8TT.

 ___
 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] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Nicholls, Mark
Ah

So it isn't a closed world

So how do I stop my instances clashing?

The x in

instance Foo Bar x

is never intended to be Integer.



Mark Nicholls | Lead broadcast  corporate architect, Programmes  Development 
- Viacom International Media Networks
A: 17-29 Hawley Crescent London NW1 8TT | e: 
nicholls.m...@vimn.commailto:m...@vimn.com T: +44 (0)203 580 2223

[Description: cid:image001.png@01CD488D.9204D030]

From: Tikhon Jelvis [mailto:tik...@jelv.is]
Sent: 05 July 2013 2:08 PM
To: Nicholls, Mark
Cc: haskell-cafe
Subject: Re: [Haskell-cafe] newbie question about Functional dependencies 
conflict between instance declarations:.


You're running into the open worldassumption--anybody could come along and 
make Integer part of your NotAnInteger class, and there's nothing you can do to 
stop them. This is a design tradeoff for typeclasses: typeclass instances are 
always global and are exported to all other modules you use. This means you 
cannot ensure a type is *not* part of a typeclass. (Or, at the very least, you 
can't convince GHC of this fact.)

For more information about this, take a look at the following StackOverflow 
question: http://stackoverflow.com/questions/8728596/explicitly-import-instances
On Jul 5, 2013 8:47 AM, Nicholls, Mark 
nicholls.m...@vimn.commailto:nicholls.m...@vimn.com wrote:
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 class Foo x y | x - y, y - x
 instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made Integer,Integer a member of it...

Something like that anyway

Then I go

 data Bar

 instance Foo Bar x

Error!but I'm think I understand thisI can't claim that Bar,x is a 
member of Foo and Integer,Integer is member of Foo and preserve my functional 
dependencies, because Bar,Integer is now a member of Foo..

Bad programmer...


So how I naively go


 class NotAnInteger a

 instance (NotAnInteger x) = Foo Bar x

I haven't declared integer to be NotAnIntegerso (in a closed 
world)this would seem to exclude the contradictionbut...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12

So

i)I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of Foo across different 
combinations of types, without them colliding.









CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK  Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.

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

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% 

[Haskell-cafe] Extending Type Classes

2013-07-05 Thread Frantisek Farka
Hello all,

I was looking for my master thesis topic and my supervisor suggested an
idea of extending class system so it enables refactoring Type Class
hierarchy without affecting client source code which is using
refactored classes. 

One example is Functor - Applicative - Monad problem and corresponding
proposal [1]. But this proposal instead of allowing the change through
extending Type Classes forces client code to prepare for the new class
layout and then switch the classes to the new layout.

My goal is rather to allow direct changes in class hierarchy without
affecting client source code. I have found different proposals
approaching this problem on HaskellWiki, some of them are overlapping,
some of them refer each other. The most promising to me seems Default
superclass instances proposal [2]. This one is somehow implemented in
the Strathclyde Haskell Enhancement (SHE) [3] but I haven't found much
reference or user experience really.

So the reason why I write this email is to ask you for some tips where
above mentioned problem occurs in real source code. I would like to
investigate some real examples before designing some ad hoc changes to
the Type Classes system.

Besides that I'd appreciate anyone who has used default superclass
instances in SHE to share his experience.

And last but not least I am always grateful for any comments and
suggestions.



Best wishes

Frantisek


[1] http://www.haskell.org/haskellwiki/Functor_hierarchy_proposal
[2] http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
[3] https://personal.cis.strath.ac.uk/conor.mcbride/pub/she/


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


[Haskell-cafe] Basic Parsec float integer parsing question

2013-07-05 Thread Fredrik Karlsson
Dear list,

Sorry for asking a simple parsec question, but both Parsec and Haskell is
new to me, so please be gentle :-)

I have this code:


import Text.ParserCombinators.Parsec
import Text.Parsec.Token
import Text.ParserCombinators.Parsec.Char


data VariableLine = VariableLine String String deriving Show
data TierType = IntervalTier | PointTier deriving Show

data Tier = Tier TierType String Float Float Integer
data Label = Interval Float Float String
data LabelFile = LabelFile Float Float

symbol :: Parser Char
symbol = oneOf !#$%|*+-/:=?@^_~

testString = intervals [1]:\nxmin = 0 \nxmax =
0.028192 \ntext = \\
headTS1 = File type = \ooTextFile\\nObject class = \TextGrid\\n\nxmin
=

header :: Parser LabelFile
header = do
headTS1
start - float
string \nxmax = 
end - float
string \ntiers? exists\nsize = 
integer
char '\n'
return $ LabelFile start end



Loading it into ghci I get :

Prelude :l parsectest.hs
[1 of 1] Compiling Main ( parsectest.hs, interpreted )

parsectest.hs:21:9:
Couldn't match type `[]'
  with `Text.Parsec.Prim.ParsecT
  String () Data.Functor.Identity.Identity'
Expected type: Text.Parsec.Prim.ParsecT
 String () Data.Functor.Identity.Identity Char
  Actual type: [Char]
In a stmt of a 'do' block: headTS1
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }

parsectest.hs:22:18:
Couldn't match expected type `Text.Parsec.Prim.ParsecT
String ()
Data.Functor.Identity.Identity Float'
with actual type `GenTokenParser s0 u0 m0
  - Text.Parsec.Prim.ParsecT s0 u0 m0
Double'
In a stmt of a 'do' block: start - float
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }

parsectest.hs:24:16:
Couldn't match expected type `Text.Parsec.Prim.ParsecT
String ()
Data.Functor.Identity.Identity Float'
with actual type `GenTokenParser s1 u1 m1
  - Text.Parsec.Prim.ParsecT s1 u1 m1
Double'
In a stmt of a 'do' block: end - float
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }

parsectest.hs:26:9:
Couldn't match expected type `Text.Parsec.Prim.ParsecT
String ()
Data.Functor.Identity.Identity a0'
with actual type `GenTokenParser s2 u2 m2
  - Text.Parsec.Prim.ParsecT s2 u2 m2
Integer'
In a stmt of a 'do' block: integer
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }
Failed, modules loaded: none.

I'm sure I'm doing something really stupid here, but I need help to get
through this problem. I've used the predefined letter parser at other
places in the code, so I can't understand why float and integer does
not work.

/Fredrik

-- 
Life is like a trumpet - if you don't put anything into it, you don't get
anything out of it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic Parsec float integer parsing question

2013-07-05 Thread David McBride
Token parsers are specific to different languages.  Afterall, haskell
parses floats differently than C, which is different from java
(probably).  In order to use it in your code you have to tell it that,
like so:

haskelldef = makeTokenParser haskellDef

header :: Parser LabelFile
header = do
  string headTS1
  start - fmap double2Float $ float haskelldef
  string \nxmax = 
  end - fmap double2Float $ float haskelldef
  string \ntiers? exists\nsize = 
  integer haskelldef
  char '\n'
  return $ LabelFile start end

You'll need to import GHC.Float (double2Float) to get those parsed
values as floats.

On Fri, Jul 5, 2013 at 12:42 PM, Fredrik Karlsson dargo...@gmail.com wrote:
 Dear list,

 Sorry for asking a simple parsec question, but both Parsec and Haskell is
 new to me, so please be gentle :-)

 I have this code:

 
 import Text.ParserCombinators.Parsec
 import Text.Parsec.Token
 import Text.ParserCombinators.Parsec.Char


 data VariableLine = VariableLine String String deriving Show
 data TierType = IntervalTier | PointTier deriving Show

 data Tier = Tier TierType String Float Float Integer
 data Label = Interval Float Float String
 data LabelFile = LabelFile Float Float

 symbol :: Parser Char
 symbol = oneOf !#$%|*+-/:=?@^_~

 testString = intervals [1]:\nxmin = 0 \nxmax = 0.028192
 \ntext = \\
 headTS1 = File type = \ooTextFile\\nObject class = \TextGrid\\n\nxmin
 =

 header :: Parser LabelFile
 header = do
 headTS1
 start - float
 string \nxmax = 
 end - float
 string \ntiers? exists\nsize = 
 integer
 char '\n'
 return $ LabelFile start end

 

 Loading it into ghci I get :

 Prelude :l parsectest.hs
 [1 of 1] Compiling Main ( parsectest.hs, interpreted )

 parsectest.hs:21:9:
 Couldn't match type `[]'
   with `Text.Parsec.Prim.ParsecT
   String () Data.Functor.Identity.Identity'
 Expected type: Text.Parsec.Prim.ParsecT
  String () Data.Functor.Identity.Identity Char
   Actual type: [Char]
 In a stmt of a 'do' block: headTS1
 In the expression:
   do { headTS1;
start - float;
string
  \
  \xmax = ;
end - float;
 }
 In an equation for `header':
 header
   = do { headTS1;
  start - float;
  string
\
\xmax = ;
   }

 parsectest.hs:22:18:
 Couldn't match expected type `Text.Parsec.Prim.ParsecT
 String () Data.Functor.Identity.Identity
 Float'
 with actual type `GenTokenParser s0 u0 m0
   - Text.Parsec.Prim.ParsecT s0 u0 m0
 Double'
 In a stmt of a 'do' block: start - float
 In the expression:
   do { headTS1;
start - float;
string
  \
  \xmax = ;
end - float;
 }
 In an equation for `header':
 header
   = do { headTS1;
  start - float;
  string
\
\xmax = ;
   }

 parsectest.hs:24:16:
 Couldn't match expected type `Text.Parsec.Prim.ParsecT
 String () Data.Functor.Identity.Identity
 Float'
 with actual type `GenTokenParser s1 u1 m1
   - Text.Parsec.Prim.ParsecT s1 u1 m1
 Double'
 In a stmt of a 'do' block: end - float
 In the expression:
   do { headTS1;
start - float;
string
  \
  \xmax = ;
end - float;
 }
 In an equation for `header':
 header
   = do { headTS1;
  start - float;
  string
\
\xmax = ;
   }

 parsectest.hs:26:9:
 Couldn't match expected type `Text.Parsec.Prim.ParsecT
 String () Data.Functor.Identity.Identity
 a0'
 with actual type `GenTokenParser s2 u2 m2
   - Text.Parsec.Prim.ParsecT s2 u2 m2
 Integer'
 In a stmt of a 'do' block: integer
 In the expression:
   do { headTS1;
start - float;
string
  \
  \xmax = ;
end - float;
 }
 In an equation for `header':
 header
   = do { headTS1;
  start - float;
  string
\
\xmax = ;
   }
 Failed, modules loaded: none.

 I'm sure I'm doing something really stupid here, but I need help to get
 through this problem. 

[Haskell-cafe] Fwd: Basic Parsec float integer parsing question

2013-07-05 Thread Antoine Latter
Forwarding to the list.


-- Forwarded message --
From: Fredrik Karlsson dargo...@gmail.com
Date: Fri, Jul 5, 2013 at 11:42 AM
Subject: [Haskell-cafe] Basic Parsec float  integer parsing question
To: haskell-cafe@haskell.org


Dear list,

Sorry for asking a simple parsec question, but both Parsec and Haskell
is new to me, so please be gentle :-)

I have this code:


import Text.ParserCombinators.Parsec
import Text.Parsec.Token
import Text.ParserCombinators.Parsec.Char


data VariableLine = VariableLine String String deriving Show
data TierType = IntervalTier | PointTier deriving Show

data Tier = Tier TierType String Float Float Integer
data Label = Interval Float Float String
data LabelFile = LabelFile Float Float

symbol :: Parser Char
symbol = oneOf !#$%|*+-/:=?@^_~

testString = intervals [1]:\nxmin = 0 \nxmax =
0.028192 \ntext = \\
headTS1 = File type = \ooTextFile\\nObject class = \TextGrid\\n\nxmin =

header :: Parser LabelFile
header = do
headTS1
start - float
string \nxmax = 
end - float
string \ntiers? exists\nsize = 
integer
char '\n'
return $ LabelFile start end



Loading it into ghci I get :

Prelude :l parsectest.hs
[1 of 1] Compiling Main ( parsectest.hs, interpreted )

parsectest.hs:21:9:
Couldn't match type `[]'
  with `Text.Parsec.Prim.ParsecT
  String () Data.Functor.Identity.Identity'
Expected type: Text.Parsec.Prim.ParsecT
 String () Data.Functor.Identity.Identity Char
  Actual type: [Char]
In a stmt of a 'do' block: headTS1
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }

parsectest.hs:22:18:
Couldn't match expected type `Text.Parsec.Prim.ParsecT
String ()
Data.Functor.Identity.Identity Float'
with actual type `GenTokenParser s0 u0 m0
  - Text.Parsec.Prim.ParsecT s0 u0 m0 Double'
In a stmt of a 'do' block: start - float
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }

parsectest.hs:24:16:
Couldn't match expected type `Text.Parsec.Prim.ParsecT
String ()
Data.Functor.Identity.Identity Float'
with actual type `GenTokenParser s1 u1 m1
  - Text.Parsec.Prim.ParsecT s1 u1 m1 Double'
In a stmt of a 'do' block: end - float
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }

parsectest.hs:26:9:
Couldn't match expected type `Text.Parsec.Prim.ParsecT
String () Data.Functor.Identity.Identity a0'
with actual type `GenTokenParser s2 u2 m2
  - Text.Parsec.Prim.ParsecT s2 u2 m2 Integer'
In a stmt of a 'do' block: integer
In the expression:
  do { headTS1;
   start - float;
   string
 \
 \xmax = ;
   end - float;
    }
In an equation for `header':
header
  = do { headTS1;
 start - float;
 string
   \
   \xmax = ;
  }
Failed, modules loaded: none.

I'm sure I'm doing something really stupid here, but I need help to
get through this problem. I've used the predefined letter parser at
other places in the code, so I can't understand why float and
integer does not work.

/Fredrik

--
Life is like a trumpet - if you don't put anything into it, you don't
get anything out of it.

___
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] same function's type accepted in top level, but rejected in where clause

2013-07-05 Thread Ömer Sinan Ağacan
Hi all,

I came across an interesting type checker error, a function is
accepted in top level, but rejected by type checker when moved to
`where ...` clause.

I moved required code to a new module for demonstration purposes:


module Bug where

fix :: (a - a) - a
fix f = let x = f x in x

data Fix f = Fix (f (Fix f))

unFix :: Fix f - f (Fix f)
unFix (Fix a) = a

data ListF a l = NilF | ConsF a l

instance Functor (ListF a) where
fmap _ NilF= NilF
fmap f (ConsF a l) = ConsF a (f l)

fold :: Functor f = (f a - a) - Fix f - a
fold f a = f (fmap (fold f) (unFix a {- f (Fix f) -}))

unfold :: Functor f = (a - f a) - a - Fix f
unfold f a = Fix (fmap (unfold f) (f a))


Now, after this code, type checker accept this function:


iterateListF :: (a - a) - a - Fix (ListF a)
iterateListF fn e = unfold (foldFn fn) e

foldFn :: (a - a) - a - ListF a a
foldFn fn a = ConsF a (fn a)


But rejects this:


iterateListF :: (a - a) - a - Fix (ListF a)
iterateListF fn e = unfold f e
  where
f :: a - ListF a a
f a = ConsF a (fn a)


With error:


bug.hs:27:20:
Couldn't match expected type `a1' with actual type `a'
  `a1' is a rigid type variable bound by
   the type signature for f :: a1 - ListF a1 a1 at bug.hs:26:10
  `a' is a rigid type variable bound by
  the type signature for
iterateListF :: (a - a) - a - Fix (ListF a)
  at bug.hs:23:17
In the return type of a call of `fn'
In the second argument of `ConsF', namely `(fn a)'
In the expression: ConsF a (fn a)


Changing type variables in type of `f` to `x` fails with this error:


bug.hs:28:20:
Couldn't match expected type `x' with actual type `a'
  `x' is a rigid type variable bound by
  the type signature for f :: x - ListF x x at bug.hs:27:10
  `a' is a rigid type variable bound by
  the type signature for
iterateListF :: (a - a) - a - Fix (ListF a)
  at bug.hs:24:17
In the return type of a call of `fn'
In the second argument of `ConsF', namely `(fn a)'
In the expression: ConsF a (fn a)
Failed, modules loaded: none.


.. and this is strange because error message describes function as it
is before changing `a` to `x`.


Any ideas why this definition rejected? Is this a bug in GHC?


---
Ömer Sinan Ağacan
http://osa1.net

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


Re: [Haskell-cafe] same function's type accepted in top level, but rejected in where clause

2013-07-05 Thread David McBride
If you remove the type signature from f in the where clause it will
work.  The reason is because the type signature listed there, the a is
a different a than in the top level signature.  If you change it from
a to x, it says it should be the a that you can't seem to specify.

If you add the pragma ScopedTypeVariables to your file, it works the
way you would assume.  However you will have to change the toplevel
signature to iterateListF :: forall a. (a - a) - a - Fix (ListF a)
in order to make it work (added the forall a.).

On Fri, Jul 5, 2013 at 4:35 PM, Ömer Sinan Ağacan omeraga...@gmail.com wrote:
 Hi all,

 I came across an interesting type checker error, a function is
 accepted in top level, but rejected by type checker when moved to
 `where ...` clause.

 I moved required code to a new module for demonstration purposes:


 module Bug where

 fix :: (a - a) - a
 fix f = let x = f x in x

 data Fix f = Fix (f (Fix f))

 unFix :: Fix f - f (Fix f)
 unFix (Fix a) = a

 data ListF a l = NilF | ConsF a l

 instance Functor (ListF a) where
 fmap _ NilF= NilF
 fmap f (ConsF a l) = ConsF a (f l)

 fold :: Functor f = (f a - a) - Fix f - a
 fold f a = f (fmap (fold f) (unFix a {- f (Fix f) -}))

 unfold :: Functor f = (a - f a) - a - Fix f
 unfold f a = Fix (fmap (unfold f) (f a))


 Now, after this code, type checker accept this function:


 iterateListF :: (a - a) - a - Fix (ListF a)
 iterateListF fn e = unfold (foldFn fn) e

 foldFn :: (a - a) - a - ListF a a
 foldFn fn a = ConsF a (fn a)


 But rejects this:


 iterateListF :: (a - a) - a - Fix (ListF a)
 iterateListF fn e = unfold f e
   where
 f :: a - ListF a a
 f a = ConsF a (fn a)


 With error:


 bug.hs:27:20:
 Couldn't match expected type `a1' with actual type `a'
   `a1' is a rigid type variable bound by
the type signature for f :: a1 - ListF a1 a1 at bug.hs:26:10
   `a' is a rigid type variable bound by
   the type signature for
 iterateListF :: (a - a) - a - Fix (ListF a)
   at bug.hs:23:17
 In the return type of a call of `fn'
 In the second argument of `ConsF', namely `(fn a)'
 In the expression: ConsF a (fn a)


 Changing type variables in type of `f` to `x` fails with this error:


 bug.hs:28:20:
 Couldn't match expected type `x' with actual type `a'
   `x' is a rigid type variable bound by
   the type signature for f :: x - ListF x x at bug.hs:27:10
   `a' is a rigid type variable bound by
   the type signature for
 iterateListF :: (a - a) - a - Fix (ListF a)
   at bug.hs:24:17
 In the return type of a call of `fn'
 In the second argument of `ConsF', namely `(fn a)'
 In the expression: ConsF a (fn a)
 Failed, modules loaded: none.


 .. and this is strange because error message describes function as it
 is before changing `a` to `x`.


 Any ideas why this definition rejected? Is this a bug in GHC?


 ---
 Ömer Sinan Ağacan
 http://osa1.net

 ___
 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] same function's type accepted in top level, but rejected in where clause

2013-07-05 Thread Ömer Sinan Ağacan
 If you add the pragma ScopedTypeVariables to your file, it works the
 way you would assume.  However you will have to change the toplevel
 signature to iterateListF :: forall a. (a - a) - a - Fix (ListF a)
 in order to make it work (added the forall a.).

Thanks, that worked.

As far as I understand, the problem is because in this definition:

where
  f :: a - ListF a a
  f a = ConsF a (fn a)

There's an implicit quantifier in type of `f`, like this: `f :: forall
a. a - ListF a a`. When I add `ScopedTypeVariables` and `forall a.
...` in top level definition, it's like all `a`s in scope of top level
definition are same, except when explicitly defined as `forall a.
...`.

Is my intuition correct?

---
Ömer Sinan Ağacan
http://osa1.net

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


[Haskell-cafe] Postdocs and Research Programmer for Compositional Learning via Generalized Automatic Differentiation

2013-07-05 Thread Barak A. Pearlmutter
We are adding exact first-class derivative calculation operators
(Automatic Differentiation or AD) to the lambda calculus, and
embodying the combination in a production-quality fast system suitable
for numeric computing in general, and compositional machine learning
methods in particular.  To the programming language community, we seek
to contribute a way to make numeric software faster, more robust, and
easier to write.

To the machine learning community, in addition to the above practical
benefits, we seek to contribute a system that embodies
*compositionality*, in that gradient optimisation can be automatically
and efficiently performed on systems themselves consisting of many
components, even when such components may internally perform
optimisation. (Examples of this include, say, optimisation of the
rules of a multi-player game to cause the players actions to satisfy
some desiderata, where the players themselves optimise their own
strategy with using a simple model of the opponent which they optimise
according to their opponent's behaviour; or multi-agent learning where
one agent learns an internal model of another agent, where that
internal model itself performs learning.)

To this end, we are seeking two postdoctoral researchers and one
research programmer with interest and experience in a cohert subset
of: programming language theory, numerics, automatic differentiation,
and machine learning.

Inquiries to: Barak A. Pearlmutter ba...@cs.nuim.ie

Informal announcment with more details:
http://www.bcl.hamilton.ie/~barak/ad-fp-positions.html, which will
have a reference to the formal announcement when it becomes available.
--
Barak A. Pearlmutter
Hamilton Institute  Dept Computer Science
NUI Maynooth
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: Ajhc Haskell Compiler 0.8.0.7 Release

2013-07-05 Thread Kiwamu Okabe
We are happy to announce Ajhc 0.8.0.7.
You can program interrupt handler with Haskell language on this release.
But not yet collect (big) patch sets, the changes will be merged to jhc.

You can get Ajhc using cabal install ajhc command.
The usage is found at Ajhc's project web site http://ajhc.metasepi.org/.
The source code at https://github.com/ajhc/ajhc/tags.

Welcome sending any bugs or your ideas to https://github.com/ajhc/ajhc/issues.

## An example of interrupt handler written with Haskell

https://github.com/ajhc/demo-cortex-m3/tree/master/stm32f3-discovery

The demo for Cortex-M4 has main context and intrrupt context.
The main context waits time expire with polling counter.
https://github.com/ajhc/demo-cortex-m3/blob/master/stm32f3-discovery/hs_src/Intr.hs#L17

The interrupt context is called from clock exception, and decrement counter.
https://github.com/ajhc/demo-cortex-m3/blob/master/stm32f3-discovery/hs_src/Intr.hs#L9

## Other changes

* Guard StablePtr critical section.
* Add _JHC_JGC_SAVING_MALLOC_HEAP option for getting smaller malloc heap.
* Link forkIO to forkOS.

Enjoy! :)
- - -
Metasepi team

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


Re: [Haskell-cafe] ANNOUNCE: Ajhc Haskell Compiler 0.8.0.7 Release

2013-07-05 Thread Adrian May
Is this a practical way to write Android and iPhone code? I don't mean
console programs, I mean realistic smartphone apps.

Seeing as smartphones outsell laptops by about 10 to 1 nowadays, it would
be nice if it was.

Adrian.
 On 6 Jul 2013 12:03, Kiwamu Okabe kiw...@debian.or.jp wrote:

 We are happy to announce Ajhc 0.8.0.7.
 You can program interrupt handler with Haskell language on this release.
 But not yet collect (big) patch sets, the changes will be merged to jhc.

 You can get Ajhc using cabal install ajhc command.
 The usage is found at Ajhc's project web site http://ajhc.metasepi.org/.
 The source code at https://github.com/ajhc/ajhc/tags.

 Welcome sending any bugs or your ideas to
 https://github.com/ajhc/ajhc/issues.

 ## An example of interrupt handler written with Haskell

 https://github.com/ajhc/demo-cortex-m3/tree/master/stm32f3-discovery

 The demo for Cortex-M4 has main context and intrrupt context.
 The main context waits time expire with polling counter.
 
 https://github.com/ajhc/demo-cortex-m3/blob/master/stm32f3-discovery/hs_src/Intr.hs#L17
 

 The interrupt context is called from clock exception, and decrement
 counter.
 
 https://github.com/ajhc/demo-cortex-m3/blob/master/stm32f3-discovery/hs_src/Intr.hs#L9
 

 ## Other changes

 * Guard StablePtr critical section.
 * Add _JHC_JGC_SAVING_MALLOC_HEAP option for getting smaller malloc heap.
 * Link forkIO to forkOS.

 Enjoy! :)
 - - -
 Metasepi team

 ___
 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