Re: carriage returns on Windows from quasi-quotes

2013-10-05 Thread Christopher Done
They're on Windows?

On 5 October 2013 01:36, Greg Weber g...@gregweber.info wrote:
 A Windows user rerported using Data.Text.IO.writeFile to write out
 quasi-quoted text.

 writeFile automatically translates '\r' to \r\n, so the user ended up
 writing out \r\r\n to a file.

 Haskell seems to be adopting the policy or removing '\r' from Haskell land.
 Is there any reason why quasi-quotes should not automatically strip carriage
 returns?

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to fix DatatypeContexts?

2013-07-18 Thread Christopher Done
Why not this?

data Pair = forall a. Eq a = Pair {x::a, y::a}
equal :: Pair - Bool
equal (Pair x y) = x == y
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to fix DatatypeContexts?

2013-07-18 Thread Christopher Done
Hm, also, with equality constraints you can make the type parametrized, too:

data Pair a' = forall a. (a ~ a', Eq a) = Pair {x::a, y::a}
equal :: Pair a - Bool
equal (Pair x y) = x == y


On 18 July 2013 13:00, Christopher Done chrisd...@gmail.com wrote:

 Why not this?

 data Pair = forall a. Eq a = Pair {x::a, y::a}
 equal :: Pair - Bool
 equal (Pair x y) = x == y


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to fix DatatypeContexts?

2013-07-18 Thread Christopher Done
Good point, classic use-case for GADTs.


On 18 July 2013 13:11, Sjoerd Visscher sjo...@w3future.com wrote:

 I'd use GADT syntax for this:

 {-# LANGUAGE GADTs #-}
 data Pair a where Pair :: Eq a = {x::a, y::a} - Pair a

 Sjoerd

 On Jul 18, 2013, at 1:05 PM, Christopher Done chrisd...@gmail.com wrote:

  Hm, also, with equality constraints you can make the type parametrized,
 too:
 
  data Pair a' = forall a. (a ~ a', Eq a) = Pair {x::a, y::a}
  equal :: Pair a - Bool
  equal (Pair x y) = x == y
 
 
  On 18 July 2013 13:00, Christopher Done chrisd...@gmail.com wrote:
  Why not this?
 
  data Pair = forall a. Eq a = Pair {x::a, y::a}
  equal :: Pair - Bool
  equal (Pair x y) = x == y
 
 
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why is GHC so much worse than JHC when computing the Ackermann function?

2013-04-20 Thread Christopher Done
JHC compiles to C and last time I tried this it looked very much like the
original C version:
http://www.reddit.com/r/haskell/comments/1bcru7/damn_lies_and_haskell_performance/c9689a3

This is the same thing. Compile with --tdir=/tmp/ajhc and then cat
/tmp/ajhc/main_code.c. Output should be like this:

static uint32_t A_STD
fW$__fMain_1__ack(gc_t gc,uint32_t v105553376,uint32_t v61835120)
{
if (0 == v105553376) {
return 1 + v61835120;
} else {
uint32_t v16;
uint32_t v22;
struct tup1 x2;
if (0 == v61835120) {
uint32_t v228308038 = (v105553376 - 1);
x2.t0 = v228308038;
x2.t1 = 1;
} else {
uint32_t v110947990;
uint32_t v215884490 = (v61835120 - 1);
uint32_t v62470112 = (v105553376 - 1);
v110947990 = fW$__fMain_1__ack(gc,v105553376,v215884490);
x2.t0 = v62470112;
x2.t1 = v110947990;
}
v22 = x2.t0;
v16 = x2.t1;
return fW$__fMain_1__ack(gc,v22,v16);
}
}

And it's as fast as C on my machine:

chris@midnight:~/Projects/me/ajhc$ time ./ack
65533

real 0m2.134s
user 0m2.124s
sys 0m0.000s
chris@midnight:~/Projects/me/ajhc$ gcc -O3 ack.c -o ack-c
ack.c: In function ‘main’:
ack.c:8:3: warning: incompatible implicit declaration of built-in function
‘printf’ [enabled by default]
chris@midnight:~/Projects/me/ajhc$ time ./ack-c
65533

real 0m2.255s
user 0m2.248s
sys 0m0.000s
chris@midnight:~/Projects/me/ajhc$




On 20 April 2013 10:55, Mikhail Glushenkov the.dead.shall.r...@gmail.comwrote:

 Hi all,

 This came up on StackOverflow [1]. When compiled with GHC (7.4.2 
 7.6.2), this simple program:

 main = print $ ack 4 1
   where ack :: Int - Int - Int
 ack 0 n = n+1
 ack m 0 = ack (m-1) 1
 ack m n = ack (m-1) (ack m (n-1))

 consumes all available memory on my machine and slows down to a crawl.
 However, when compiled with JHC it runs in constant space and is about
 as fast as the straightforward Ocaml version (see the SO question for
 benchmark numbers).

 I was able to fix the space leak by using CPS-conversion, but the
 CPS-converted version is still about 10 times slower than the naive
 version compiled with JHC.

 I looked both at the Core and Cmm, but couldn't find anything
 obviously wrong with the generated code - 'ack' is compiled to a
 simple loop of type 'Int# - Int# - Int#'. What's more frustrating is
 that running the program with +RTS -hc makes the space leak
 mysteriously vanish.

 Can someone please explain where the space leak comes from and if it's
 possible to further improve the runtime of this program with GHC?
 Apparently it's somehow connected to the stack management strategy,
 since running the program with a larger stack chunk size (+RTS -kc1M)
 makes the space leak go away. Interestingly, choosing smaller stack
 chunk sizes (256K, 512K) causes it to die with an OOM exception:

 $ time ./Test +RTS -kc256K
 Test: out of memory (requested 2097152 bytes)


 [1]
 http://stackoverflow.com/questions/16115815/ackermann-very-inefficient-with-haskell-ghc/16116074#16116074

 --
 ()  ascii ribbon campaign - against html e-mail
 /\  www.asciiribbon.org   - against proprietary attachments

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to get started with a new backend?

2013-01-27 Thread Christopher Done
 The trac claims that ghc can compile itself to C so that only standard gnu C 
 tools are needed to build an unregistered compiler.

Wait, it can? Where's that?

On 28 January 2013 02:15, Jason Dagit dag...@gmail.com wrote:
 I would like to explore making a backend for .NET. I've done a lot of
 background reading about previous .NET and JVM attempts for Haskell. It
 seems like several folks have made significant progress in the past and,
 with the exception of UHC, I can't find any code around the internet from
 the previous efforts. I realize that in total it's a huge undertaking and
 codegen is only one of several significant hurdles to success.

 I would like to get a very, very, very simple translation working inside
 GHC. If all I can compile and run is fibonacci, then I would be quite happy.
 For my first attempt, proof of concept is sufficient.

 I found a lot of good documentation on the ghc trac for how the compilation
 phases work and what happens in the different parts of the backend. The
 documentation is excellent, especially compared to other compilers I've
 looked at.

 When I started looking at how to write the code, I started to wonder about
 the least effort path to getting something (anything?) working. Here are
 some questions:
   * Haskell.NET seems to be dead. Does anyone know where their code went?
   * Did lambdavm also disappear? (JVM I know, but close enough to be useful)
   * Would it make sense to copymodify the -fvia-C backend to generate C#?
 The trac claims that ghc can compile itself to C so that only standard gnu C
 tools are needed to build an unregistered compiler. Could I use this trick
 to translate programs to C#?
   * What stage in the pipeline should I translate from? Core? STG? Cmm?
   * Which directories/source files should I look at to get familiar with the
 code gen? I've heard the LLVM codegen is relatively simple.
   * Any other advice?

 Thank you in advance!
 Jason

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: UHC-like JavaScript backend in GHC

2012-11-13 Thread Christopher Done
On 13 November 2012 16:33, J. Stutterheim j.stutterh...@me.com wrote:
 Yes, I did check out other work that's been done in this area, albeit only 
 briefly. Unless I've overlooked it (which is very much possible), none of the 
 other solutions (except Fay) support an FFI that bridges the gap between JS's 
 OO and the functional world, like our JS-like language in the foreign 
 imports. In real-life situations, where you want to get rid of writing JS 
 entirely, but still might want to use existing JS libraries such as jQuery, 
 this feature is essential.

Just a small point, but Fay's FFI differs from UHC/GHC's in that it
natively supports String/Double and functions without needing wrappers
and conversions from CString or whatnot. E.g. you write

addClassWith :: (Double - String - Fay String) - JQuery - Fay JQuery
addClassWith = ffi %2.addClass(%1)

and you're already ready to use it. If I recall in UHC last I tried, I
had to do some serializing/unserializing for the string types, and
make a wrapper function for the callback. Whether it makes any sense
for a UHC/GHC-backend to behave like this, I don't know. But people
really like it.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: UHC-like JavaScript backend in GHC

2012-11-13 Thread Christopher Done
You also need an accomplice web server to host the JS file containing
the JavaScript for the web worker to run. I don't see how you can
fork threads without such support.

On 13 November 2012 20:53, Luite Stegeman stege...@gmail.com wrote:
 Does/can cabal-install support GHCJS? I suppose that's a minor advantage of 
 extending GHC itself; you get cabal support almost for free.

 Yes. There are two GHCJS installation options. One is the standalone
 option that includes wrappers for cabal and ghc-pkg. You use
 `ghcjs-cabal` to install packages, see the result with `ghcjs-pkg
 list`. The standalone compiler can be installed with cabal-install,
 but it does require you to run `ghcjs-boot` in a configured GHC source
 tree, to install the core libraries (ghc-prim, base, integer-gmp).

 The alternative is the integrated compiler, where you completely
 replace your existing GHC with one that can output Javascript. You
 don't get separate package databases this way.

 How big are the JS files generated with either the new or the old code 
 generator? I recall there was a HS - JS effort out there that generated 
 huge JS files. UHC's output is relatively compact and doesn't grow as fast 
 with bigger programs.

 Relatively big for the new generator because I haven't focused on this
 yet. The generated code has lots of redundant assignments that can be
 weeded out later with a dataflow analysis pass. The old generator is a
 bit more compact (similar to haste compiler). Both versions have a
 function-level linker that only includes functions that are actually
 used.

 WebWorkers is quite limited indeed. I'm not yet sure how the serialisation 
 might complicate matters, but it seems that WebWorkers is only really a 
 possible backend for `fork`, and not `forkIO`.

 For one, you cannot serialize closures, so it will probably be similar
 to the restrictions in Cloud Haskell in that you can only call
 top-level things on the other side (Unless you don't use Javascript
 closures for your Haskell closures, the new GHCJS generator can
 actually move closures to a WebWorker, at least in theory, it's not
 yet implemented)

 luite

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GADTs in the wild

2012-08-18 Thread Christopher Done
On 18 August 2012 20:57, Bertram Felgenhauer
bertram.felgenha...@googlemail.com wrote:
 The natural encoding as a GADT would be as follows:

 data Command result where
 GetFoo :: Double - Command Foo
 PutFoo :: String - Command Double


Right, that's exactly what I wrote at the end of my email. And then
indeed dispatch would be `dispatch :: Command a - Snap a`. But how do
you derive an instance of Typeable and Read for this data type? The
Foo and the Double conflict and give a type error.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GADTs in the wild

2012-08-17 Thread Christopher Done
Funny, I just solved a problem with GADTs that I couldn't really see how
to do another way.


The context
===

In a fat-client web app (like GMail) you have the need to send requests
back to the server to notify the server or get information back, this is
normally transported in JSON format. For a Haskell setup, it would be:

JavaScript (Client) → JSON → Haskell (Server)

I made Fay, a Haskell subset that compiles to JavaScript to displace
JavaScript in this diagram and now it's:

Haskell (Client) → JSON → Haskell (Server)


Three problems to solve
===

There are three problems that I wanted to solve:

1. Make serialization just work, no writing custom JSON instances or
whatnot. That problem is solved. So I can just write:

get some-request $ \(Foo bar mu) - …

2. Share data type definitions between the client and server code. That
problem is solved, at least I have a solution that I like. It's like
this:

module SharedTypes where
… definitions here …

module Client where
import SharedTypes

module Server where
import SharedTypes

Thus, after any changes to the data types, GHC will force the programmer
to update the server AND the client. This ensures both systems are in
sync with one-another. A big problem when you're working on large
applications, and a nightmare when using JavaScript.

3. Make all requests to the server type-safe, meaning that a given
request type can only have one response type, and every command which is
possible to send the server from the client MUST have a response. I have
a solution with GADTs that I thing is simple and works.


The GADTs part
==

module SharedTypes where

I declare my GADT of commands, forcing the input type and the return
type in the parameters. The Foreign instance is just for Fay to allow
things to be passed to foreign functions.

-- | The command list.
data Command where
  GetFoo :: Double - Returns Foo - Command
  PutFoo :: String - Returns Double - Command
  deriving Read
instance Foreign Command

Where `Returns' is a simple phantom type. We'll see why this is
necessary in a sec.

-- | A phantom type which ensures the connection between the command
-- and the return value.
data Returns a = Returns
  deriving Read

And let's just say Foo is some domain structure of interest:

-- | A foobles return value.
data Foo = Foo { field1 :: Double, field2 :: String, field3 :: Bool }
  deriving Show
instance Foreign Foo

Now in the Server module, I write a request dispatcher:

-- | Dispatch on the commands.
dispatch :: Command - Snap ()
dispatch cmd =
  case cmd of
GetFoo i r - reply r (Foo i Sup? True)

Here is the clever bit. I need to make sure that the response Foo
corresponds to the GetFoo command. So I make sure that any call to
`reply` must give a Returns value. That value will come from the nearest
place; the command being dispatched on. So this, through GHC's pattern
match exhaustion checks, ensures that all commands are handled.

-- | Reply with a command.
reply :: (Foreign a,Show a) = Returns a - a - Snap ()
reply _ = writeLBS . encode . showToFay

And now in the Client module, I wanted to make sure that GetFoo can only
be called with Foo, so I structure the `call` function to require a
Returns value as the last slot in the constructor:

-- | Call a command.
call :: Foreign a = (Returns a - Command) - (a - Fay ()) - Fay ()
call f g = ajaxCommand (f Returns) g

The AJAX command is a regular FFI, no type magic here:

-- | Run the AJAX command.
ajaxCommand :: Foreign a = Command - (a - Fay ()) - Fay ()
ajaxCommand =
  ffi jQuery.ajax({url: '/json', data: %1,\
  dataType: 'json', success : %2 })

And now I can make the call:

-- | Main entry point.
main :: Fay ()
main = call (GetFoo 123) $ \(Foo _ _ _) - return ()


Summary
===

So in summary I achieved these things:

* Automated (no boilerplate writing) generation of serialization for
  the types.
* Client and server share the same types.
* The commands are always in synch.
* Commands that the client can use are always available on the server
  (unless the developer ignored an incomplete-pattern match warning, in
  which case the compiler did all it could and the developer deserves
  it).

I think this approach is OK. I'm not entirely happy about reply r. I'd
like that to be automatic somehow.


Other approaches / future work
==

I did try with:

data Command a where
  GetFoo :: Double - Command Foo
  PutFoo :: String - Command Double

But that became difficult to make an automatic decode instance. I read
some suggestions by Edward Kmett:
http://www.haskell.org/pipermail/haskell-cafe/2010-June/079402.html

But it looked rather hairy to do in an automatic way. If anyone has any
improvements/ideas to achieve this, please let me know.


Re: GADTs in the wild

2012-08-17 Thread Christopher Done
Oh, I went for a walk and realised that while I started with a GADT, I
ended up with a normal Haskell data type in a fancy GADT dress. I'll
get back to you if I get the GADT approach to work.

On 17 August 2012 15:14, Christopher Done chrisd...@gmail.com wrote:
 Funny, I just solved a problem with GADTs that I couldn't really see how
 to do another way.


 The context
 ===

 In a fat-client web app (like GMail) you have the need to send requests
 back to the server to notify the server or get information back, this is
 normally transported in JSON format. For a Haskell setup, it would be:

 JavaScript (Client) → JSON → Haskell (Server)

 I made Fay, a Haskell subset that compiles to JavaScript to displace
 JavaScript in this diagram and now it's:

 Haskell (Client) → JSON → Haskell (Server)


 Three problems to solve
 ===

 There are three problems that I wanted to solve:

 1. Make serialization just work, no writing custom JSON instances or
 whatnot. That problem is solved. So I can just write:

 get some-request $ \(Foo bar mu) - …

 2. Share data type definitions between the client and server code. That
 problem is solved, at least I have a solution that I like. It's like
 this:

 module SharedTypes where
 … definitions here …

 module Client where
 import SharedTypes

 module Server where
 import SharedTypes

 Thus, after any changes to the data types, GHC will force the programmer
 to update the server AND the client. This ensures both systems are in
 sync with one-another. A big problem when you're working on large
 applications, and a nightmare when using JavaScript.

 3. Make all requests to the server type-safe, meaning that a given
 request type can only have one response type, and every command which is
 possible to send the server from the client MUST have a response. I have
 a solution with GADTs that I thing is simple and works.


 The GADTs part
 ==

 module SharedTypes where

 I declare my GADT of commands, forcing the input type and the return
 type in the parameters. The Foreign instance is just for Fay to allow
 things to be passed to foreign functions.

 -- | The command list.
 data Command where
   GetFoo :: Double - Returns Foo - Command
   PutFoo :: String - Returns Double - Command
   deriving Read
 instance Foreign Command

 Where `Returns' is a simple phantom type. We'll see why this is
 necessary in a sec.

 -- | A phantom type which ensures the connection between the command
 -- and the return value.
 data Returns a = Returns
   deriving Read

 And let's just say Foo is some domain structure of interest:

 -- | A foobles return value.
 data Foo = Foo { field1 :: Double, field2 :: String, field3 :: Bool }
   deriving Show
 instance Foreign Foo

 Now in the Server module, I write a request dispatcher:

 -- | Dispatch on the commands.
 dispatch :: Command - Snap ()
 dispatch cmd =
   case cmd of
 GetFoo i r - reply r (Foo i Sup? True)

 Here is the clever bit. I need to make sure that the response Foo
 corresponds to the GetFoo command. So I make sure that any call to
 `reply` must give a Returns value. That value will come from the nearest
 place; the command being dispatched on. So this, through GHC's pattern
 match exhaustion checks, ensures that all commands are handled.

 -- | Reply with a command.
 reply :: (Foreign a,Show a) = Returns a - a - Snap ()
 reply _ = writeLBS . encode . showToFay

 And now in the Client module, I wanted to make sure that GetFoo can only
 be called with Foo, so I structure the `call` function to require a
 Returns value as the last slot in the constructor:

 -- | Call a command.
 call :: Foreign a = (Returns a - Command) - (a - Fay ()) - Fay ()
 call f g = ajaxCommand (f Returns) g

 The AJAX command is a regular FFI, no type magic here:

 -- | Run the AJAX command.
 ajaxCommand :: Foreign a = Command - (a - Fay ()) - Fay ()
 ajaxCommand =
   ffi jQuery.ajax({url: '/json', data: %1,\
   dataType: 'json', success : %2 })

 And now I can make the call:

 -- | Main entry point.
 main :: Fay ()
 main = call (GetFoo 123) $ \(Foo _ _ _) - return ()


 Summary
 ===

 So in summary I achieved these things:

 * Automated (no boilerplate writing) generation of serialization for
   the types.
 * Client and server share the same types.
 * The commands are always in synch.
 * Commands that the client can use are always available on the server
   (unless the developer ignored an incomplete-pattern match warning, in
   which case the compiler did all it could and the developer deserves
   it).

 I think this approach is OK. I'm not entirely happy about reply r. I'd
 like that to be automatic somehow.


 Other approaches / future work
 ==

 I did try with:

 data Command a where
   GetFoo :: Double - Command Foo

Re: Why GHC doesn't warn about LHS nullary-constructor pattern bindings?

2012-07-19 Thread Christopher Done
In your case the Nothing is unused so will never be a problem.

Perhaps more worrying:

foo :: Int - Int
foo n = x + 1
where
  Just x = Nothing

This gives no warnings.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Christopher Done
Depends what the real offending code is. For example, if it contains
unsafePerformIO then it's not a bug.

On 10 July 2012 12:42, Sönke Hahn sh...@cs.tu-berlin.de wrote:
 Hi!

 I've discovered a strange bug that violates simple equational reasoning.
 Basically, something similar to this:

 let a = f x
 in a == f x

 evaluates to False.

 I'd like to report this on ghc-trac, but I realised, that I don't know a
 good name for behaviour like this. Is there one? Broken referential
 transparency, perhaps?

 Thanks,
 Sönke


 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-05 Thread Christopher Done
I like \case as is proposed. It seems the least controversial one and
there's curry (\case ) for two-args, but even that seems a rare case.

For what it's worth, I like the idea of omission being partiality, as
in case of and if then. It seems perfectly natural to me, I don't need
a \ to tell me that an expression will result in a function. But some
do. So I'll go along with and vote for \case. The lack of a lambda
case is one of the few legitimate complaints I have about Haskell's
syntax so it would be marvey to see it in GHC.

P.S. \if then … else …?

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Explicit calls to the garbage collector.

2012-05-07 Thread Christopher Done
I would also be interested to know this. A web server is an example of
a Haskell program that could force garbage collection at the end of
every request reply, especially a multi-threaded server where the
memory use is localized to threads. For long-running applications, a
GC at this point would be nice.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-21 Thread Christopher Done
Pretty sure it does default to String, anyway:

{-# LANGUAGE OverloadedStrings #-}

main = print (show Hello!)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] A Modest Records Proposal

2012-04-02 Thread Christopher Done
On 2 April 2012 14:41, Michael Snoyman mich...@snoyman.com wrote:
 import Data.Time

 main = do
    now - getCurrentTime
    let (_, month, day) = toGregorian $ utctDay now
    putStrLn $
        if month == 4  day == 1
            then It's a joke
            else It's real

import Data.Time
main = do
   now - getCurrentTime
   let (_, month, day) = toGregorian $ utctDay now
   putStrLn $
   if month == 4  day == 1
   then It's a joke
   else It's real. (This output is not a joke. But run this
program again to be sure.)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] A Modest Records Proposal

2012-04-01 Thread Christopher Done
I actually read the first couple paragraphs and thought “sounds
interesting I'll read it later”. After reading it properly, I lol'd.

 After some initial feedback, I'm going to create a page for the
 Homotopy Extensional Records Proposal (HERP) on trac. There are really
 only a few remaining questions. 1) Having introduced homotopies, why
 not go all the way and introduce dependent records? In fact, are HERP
 and Dependent Extensional Records Proposal (DERP) already isomorphic?
 My suspicion is that HERP is isomorphic, but DERP is not.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCi and line numbers (with ghc-7.4.1)

2012-03-22 Thread Christopher Done
On 22 March 2012 12:13, Simon Marlow marlo...@gmail.com wrote:
 On 20/03/2012 20:12, Simon Hengel wrote:
 They are now incremented with each evaluated expression.

Why *are* they incremented with each evaluation? Surely the only use
for line numbers would be in multi-line statements:

 :{
Prelude| do x - [1..10]
Prelude|    return y
Prelude| :}

interactive:6:11: Not in scope: `y'

Would it not make more sense to have

interactive:2:11: Not in scope: `y'

as it would do if compiling the file in a source file? From the older
GHCs, this always gives 1, indicating that multi-line statements are
somehow parsed and collapsed before being compiled, or maybe the line
number was just hard coded to 1.

FWIW, in my Emacs mode (making good progress on adding to
haskell-mode) I use the column number in the REPL to highlight on the
line where the problem is (e.g. here
http://chrisdone.com/images/hs-repl-error-demo.png), for GHC 7.* with
proper multi-line support I will automatically wrap any multi-line
expressions entered in the REPL in :{ and :}, it would be cool for
line numbers in errors to be useful for that. (Arguably we should be
using the GHC API and Scion or something like it, but these change
quite often and are hard to support whereas interfacing with GHCi is
quite stable across around seven releases and just works.)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to work around GHC bug

2012-03-14 Thread Christopher Done
On 14 March 2012 15:08, Ozgur Akgun ozgurak...@gmail.com wrote:

 On 14 March 2012 13:51, Volker Wysk p...@volker-wysk.de wrote:

 import System

 main = do

 [a] - getArgs

 putStrLn (show a)


 a here is already of type String. If you don't call show on it, it'll do
 the expected thing.


He means that the UTF-8 encoded string passed to the program should be
decoded into unicode points into Chars. So putStrLn (length a) should be 1
were it decoded, but it's actually 2. You can't use this string properly,
there is no Char containing the ä.  See?
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
I added my evaluation of the module-based approach to existing
records, but on second thoughts it's maybe inappropriate, so I'll post
it here. I saw that some people commented on the reddit discussion
that the solution is to put your types in separate modules but it
doesn't seem that anyone has tried to do this on a large scale. I
tried it (and some other record paradigms including Has), but I don't
think it scales. Here's why…

Suppose I have 112 hand-crafted data types in my
project (e.g. see attachment 51369.txt[1]), this creates a lot of
conflicts in field names and constructor names. For example:

{{{
data Comment = Comment {
  commentId   :: CommentId
, commentContent  :: Content
, commentReviewId :: ReviewId
, commentSubmissionId :: SubmissionId
, commentConferenceId :: ConferenceId
, commentDate :: ISODate
, commentReviewerNumber :: Int
  } deriving (Show)
}}}

This is a real type in my project. It has fields like “id”, “content”,
“reviewId”, “submissionId”, “date”. There are seven other data types
that have a field name “submissionId”. There are 15 with
“conferenceId”. There are 7 with “content”. And so on. This is just to
demonstrate that field clashes ''do'' occur ''a lot'' in a nontrivial
project.

It also demonstrates that if you propose to put each of these 112 types
into a separate module, you are having a laugh. I tried this around
the 20 type mark and it was, apart from being very slow at compiling,
''very'' tedious to work with. Creating and editing these modules was a
distracting and pointless chore.

It ''also'' demonstrated, to me, that qualified imports are horrible
when used on a large scale. It happened all the time, that'd I'd
import, say, 10 different data types all qualified.  Typing map
(Foo.id . BarMu.thisField) and foo Bar.Zot{x=1,y=2} becomes tedious
and distracting, especially having to add every type module when I
want to use a type. And when records use other types in other modules,
you have ''a lot'' of redundancy. With the prefixing paradigm I'd write
fooId and barMuThisField, which is about as tedious but there is at
least less . confusion and no need to make a load of modules and
import lines. Perhaps local modules would solve half of this
problem. Still have to write “Bar.mu bar” rather than “mu bar”, but
it'd be an improvement.

I also have 21 Enum types which often conflict. I end up having to
include the name of the type in the constructor, or rewording it
awkwardly. I guess I should put these all in separate modules and
import qualified,
too. Tedious, though. At least in this case languages like C# and
Java also require that you type EnumName.EnumValue, so c‘est la vie.

[1]: http://hackage.haskell.org/trac/ghc/attachment/wiki/Records/51369.txt

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
TRex is already mentioned on the wiki as coming at a too high
implementation cost.

2011/9/15 J. Garrett Morris jgmor...@cs.pdx.edu:
 On Thu, Sep 15, 2011 at 6:03 AM, Barney Hilken b.hil...@ntlworld.com wrote:
 The right way to deal with records is first to agree a mechanism for
 writing a context which means

        a is a datatype with a field named n of type b

 then give the selector n the type

        a is a datatype with a field named n of type b = n :: a - b

 There is no reason why this shouldn't be used with the current syntax
 (although it might clash with more advanced features like first-class
 labels).

 Trex is one existing approach in the Haskell design space
 http://web.cecs.pdx.edu/~mpj/pubs/polyrec.html
 http://web.cecs.pdx.edu/~mpj/pubs/lightrec.html

  /g

 --
 I’m surprised you haven’t got a little purple space dog, just to ram
 home what an intergalactic wag you are.

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
I personally really like the proposal here:
http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html

The wiki doesn't show any opposition to this system. If Haskell had
that record system now I would be very happy and would be fine with
leaving other record systems as purely research until this whole
research area comes to some decisions.

 I believe the way forward is to implement several of the possible systems, 
 and release them for feedback. To get users to actually try out the 
 libraries, I think we need some concrete syntax for constant records, so I 
 suggest we put in a feature request.

It would also be nice if one saintly person could spend the time
documenting the available record systems in one document, trying out
examples of codebases and collecting surveys on the various systems or
something. It's a project in itself.

Personally my vote for what it's worth is Worse is Better in this
case, and to implement Simon's proposal (not that I think this
proposal is Worse, but possibly worse than
X-other-really-nice-but-tough-to-decide-on-system). If we still have
nothing by this time in six months I'll implement the bloody thing in
GHC myself.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
2011/9/15 Greg Weber g...@gregweber.info:
 Chris, Thank you for the real word experience report. I had assumed (because
 everyone else told me) that importing qualified would be much, much better
 than prefixing. I had thought that in your case since you are big on model
 separation that you would have liked having a separate file for each model
 to separate out all your model related code with. As a counter point, in all
 of my (MVC) web application projects, we do have a separate file for each
 model, and we like this approach. Each file usually contains a lot of
 business logic related to the model- the only relatively empty model files
 are ones that really represent embedded data. When I use MongoDB (which
 actually supports embedded data instead of forcing you to create a separate
 table), I will actually place the embedded models in the same file as the
 model which includes them.

Ah, this is because my approach to types is to put them in a
ProjectName.Types.X module. I /do/ have separate modules for all my
models, e.g.

$ ls Confy/Model/*.hs
Confy/Model/Actions.hs Confy/Model/Driver.hs
Confy/Model/Manuscript.hsConfy/Model/Proceedings.hs 
Confy/Model/SubmissionAuthor.hs  Confy/Model/Token.hs
Confy/Model/Activity.hsConfy/Model/Fields.hs
Confy/Model/Message.hs   Confy/Model/ReviewComment.hs   
Confy/Model/Submission.hsConfy/Model/Track.hs
Confy/Model/Author.hs  Confy/Model/FormField.hs
Confy/Model/Papertype.hs Confy/Model/ReviewerPreference.hs
Confy/Model/Tables.hsConfy/Model/User.hs
Confy/Model/Conference.hs  Confy/Model/Form.hs  
Confy/Model/Participant.hs  Confy/Model/Review.hs   
Confy/Model/Template.hs  Confy/Model/UserMeta.hs
Confy/Model/Deadline.hsConfy/Model/LogEntry.hs
Confy/Model/Period.hsConfy/Model/Role.hsConfy/Model/TH.hs   

 Confy/Model/Utils.hs

I have my HaskellDB types and then I have my normal Haskell types
which contain different fields to the database model.

But to put the /type/ in the model file itself causes cyclic import
problems when I have to start caring about what imports what and then
having modules that just contain types, etc. I find this to be quite
laborious, I did it at first but it became a hindrance to development
practice for me. Have you not found that you have this problem if you
put types in the same modules as code in a large project? Examples
welcome, too.

 After my blog post complaining about records, I had a few people telling me
 that I can just use existing polymorphism to avoid the name-spacing issue. I
 collected the approaches here: http://www.yesodweb.com/wiki/record-hacks
 I didn't think any of those telling me what i should do had actually tried
 to do this themselves, particularly at any kind of larger scale. I am
 interested to see if anyone has experience trying this approach, or if you
 have considered it.

I considered that approach but never tried it, one would probably
enlist the help of TemplateHaskell to do that approach properly. Maybe
it's not so bad? I suppose I could try making a few branches in my
project and try out this approach.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
2011/9/15 Greg Weber g...@gregweber.info:
 I should be clear that in my counter point I am using Ruby, not Haskell on
 those projects. In Ruby one can use a string for the name of a class (which
 will be evaluated later) and other general dynamic typing tricks to avoid
 cyclical dependencies.

Ah, okay. Sure, late binding (that's what it's called) makes it convenient.

 I have worked on one large Yesod project. I felt they were creating
 artificially shortened field names in some cases (that I found difficult to
 understand/remember) to try and ease the pain of large prefixed record
 selectors.

I can understand that. Accessors like reviewAssignSubmissionId for a
ReviewAssign record are pretty tedious but at least I don't have
trouble remembering them.

 However, Yesod does create all the records with prefixes in one
 module/file- so all the types are in there. They create a new model file for
 each model (conceptually, but not for a model representing simple embedded
 data). The model file can import all the record types.

Right, that's what I do. Types in one big types file, and then the
functions for the model in Project.Model.X which imports the types
file. This is an internal project, but it will be released as open
source in a few months so showing you the haddock output isn't a big
deal: http://chrisdone.com/confy-doc/ My militantness regarding adding
haddock docs is scant due to deadline pressures as you'd expect, but
it's not so bad.

E.g. checkout http://chrisdone.com/confy-doc/Confy-Model-Conference.html
and it's blatant I'm using a lot of other types.

All entities or entity-like things are in:
http://chrisdone.com/confy-doc/Confy-Types-Entities.html and enums in
http://chrisdone.com/confy-doc/Confy-Types-Enums.html

And do not look at
http://chrisdone.com/confy-doc/Confy-Model-Tables.html because it is
frightening and will make you go bald. If you're already bald, feel
free! HaskellDB and its HList-like record system.

 Personally I would prefer to define my type in the model file so I can
 quickly see my type with the related code if it were possible, but it seems
 that it isn't.

I guess it can be possible with a lot of discipline and patience.
Maybe others have done this in large projects and found it not so bad?

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users