Re: [Haskell-cafe] catching IO errors in a monad transformer stack

2013-07-19 Thread Eric Rasmussen
Thanks Alberto!

I was able to derive MonadCatchIO for my stack and generalize my IO error
handling to:

{-# LANGUAGE FlexibleContexts #-}

import Prelude hiding (catch)

import Control.Monad.Error
import Control.Monad.State
import Control.Monad.CatchIO

import System.IO.Error (tryIOError)
import Control.Exception (IOException)

guardIO :: (MonadCatchIO m, MonadError String m) = IO a - m a
guardIO action =
  liftIO action `catch` \e - throwError $ show (e :: IOException)

As David mentioned it can be better to leave this to the individual, but it
seems like it would be fairly common to want a drop-in replacement for
liftIO that would automatically handle IO exceptions using ErrorT instead
of breaking the flow of the program or requiring the developer to catch
everything separately.

My example above might be too specific because not everyone will represent
errors with String when using ErrorT, but we could accommodate that with:

guardIO' :: (MonadCatchIO m, MonadError e m) = IO a - (IOException - e)
- m a
guardIO' action convertExc =
  liftIO action `catch` \e - throwError $ convertExc e

Would there be any interest in cleaning that up and adding it (or something
similar) to Control.Monad.CatchIO?

Either way I will write up a blog post on it since I couldn't find any
tutorials breaking this process down.

Thanks everyone!








On Thu, Jul 18, 2013 at 4:23 PM, Alberto G. Corona agocor...@gmail.comwrote:

 Hi Eric:

 The pattern may be the MonadCatchIO class:

 http://hackage.haskell.org/package/MonadCatchIO-transformers


 2013/7/18 Eric Rasmussen ericrasmus...@gmail.com

 Hello,

 I am writing a small application that uses a monad transformer stack, and
 I'm looking for advice on the best way to handle IO errors. Ideally I'd
 like to be able to perform an action (such as readFile
 file_that_does_not_exist), catch the IOError, and then convert it to a
 string error in MonadError. Here's an example of what I'm doing now:

 {-# LANGUAGE FlexibleContexts #-}

 import Control.Monad.Error
 import Control.Monad.State

 import System.IO.Error (tryIOError)

 catcher :: (MonadIO m, MonadError String m) = IO a - m a
 catcher action = do
   result - liftIO $ tryIOError action
   case result of
 Left  e - throwError (show e)
 Right r - return r

 This does work as expected, but I get the nagging feeling that I'm
 missing an underlying pattern here. I have tried catch, catchError, and
 several others, but (unless I misused them) they don't actually help here.
 The tryIOError function from System.IO.Error is the most helpful, but I
 still have to manually inspect the result to throwError or return to my
 underlying monad.

 Since this has come up for me a few times now, I welcome any advice or
 suggestions on alternative approaches or whether this functionality already
 exists somewhere.

 Thanks!
 Eric






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




 --
 Alberto.

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


Re: [Haskell-cafe] Generating Haskell Code out of Haskell AST (GHC API)

2013-07-19 Thread John Blackbox
Thank you!
So, if I'm writing a compiler of custom language, which I want to generate
Haskell AST and further compile it with GHC, you prefer something like
haskell-src-exts
over pure GHC API?


2013/7/19 Antoine Latter aslat...@gmail.com

 The package haskell-src-exts is a lot less intimidating if all you are
 trying to do is programmatically generate Haskell source:

 http://hackage.haskell.org/package/haskell-src-exts

 The base types are here:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Syntax.html#t:Module

 This module has some helper function for generating parts of the AST:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Build.html


 On Thu, Jul 18, 2013 at 1:11 PM, John Blackbox
 blackbox.dev...@gmail.com wrote:
  Hi!
  I dont know GHC API very well, but I want to generate AST of a program
 using
  GHC API.
  Is there any standard method to generate Haskell code out of it?
 (something
  like print_this_for_me_please function? :D
 
  ___
  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] Generating Haskell Code out of Haskell AST (GHC API)

2013-07-19 Thread John Blackbox
I accidentally didn't send that email to haskell-cafe, so I'm pasting it
here also:

Alan - I do NOT want to generate Haskell code. I want only to generate AST
and compile it.
The question about generating the code was only to have a debugging tool
- to see if the generated AST is good - I wanted to generate the Haskell
code only to check if its correct, but normally I would not do it, because
it makes no sense to generate AST - code - AST (by GHC) again etc :)
Additional - I want to connect to GHC's type-checking also and translate
the errors to be appropriate to my language syntax - so maybe the pure GHC
API is the best way to go?


2013/7/19 John Blackbox blackbox.dev...@gmail.com

 Additional - I want to connect to GHC's type-checking also and translate
 the errors to be appropriate to my language syntax.


 2013/7/19 John Blackbox blackbox.dev...@gmail.com

 Alan - I do NOT want to generate Haskell code. I want only to generate
 AST and compile it.
 The question about generating the code was only to have a debugging
 tool - to see if the generated AST is good - I wanted to generate the
 Haskell code only to check if its correct, but normally I would not do it,
 because it makes no sense to generate AST - code - AST (by GHC) again etc
 :)


 2013/7/19 AlanKim Zimmerman alan.z...@gmail.com

 I have not used haskell-src-exts so I may be talking out of turn, but it
 seems that if you want to generate an AST which you then turn into source
 code and compile it makes more sense than using than GHC AST, which has a
 number of wrinkles, including fields that are only valid at certain phases
 of the compilation process.

 For my purposes, in the Haskell Refactorer, I need access to the
 renaming and type-checking, which to my knowledge is not currently
 available in haskell-src-exts, although there is work happening to bring it
 in, e.g. https://github.com/haskell-suite/haskell-names.


 On Fri, Jul 19, 2013 at 10:09 AM, John Blackbox 
 blackbox.dev...@gmail.com wrote:

 Thank you!
 So, if I'm writing a compiler of custom language, which I want to
 generate Haskell AST and further compile it with GHC, you prefer
 something like haskell-src-exts over pure GHC API?


 2013/7/19 Antoine Latter aslat...@gmail.com

 The package haskell-src-exts is a lot less intimidating if all you are
 trying to do is programmatically generate Haskell source:

 http://hackage.haskell.org/package/haskell-src-exts

 The base types are here:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Syntax.html#t:Module

 This module has some helper function for generating parts of the AST:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Build.html


 On Thu, Jul 18, 2013 at 1:11 PM, John Blackbox
 blackbox.dev...@gmail.com wrote:
  Hi!
  I dont know GHC API very well, but I want to generate AST of a
 program using
  GHC API.
  Is there any standard method to generate Haskell code out of it?
 (something
  like print_this_for_me_please function? :D
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



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





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


Re: [Haskell-cafe] Generating Haskell Code out of Haskell AST (GHC API)

2013-07-19 Thread Daniel Trstenjak

Hi John,

 Alan - I do NOT want to generate Haskell code. I want only to generate AST
 and compile it.
 The question about generating the code was only to have a debugging tool
 - to see if the generated AST is good - I wanted to generate the Haskell
 code only to check if its correct, but normally I would not do it, because
 it makes no sense to generate AST - code - AST (by GHC) again etc :)
 Additional - I want to connect to GHC's type-checking also and translate
 the errors to be appropriate to my language syntax - so maybe the pure GHC
 API is the best way to go?

I don't know what kind of language you're writing, but I don't think
that this is the easiest approach.

Just trying to convert a GHC error in something meaningful for your
language sounds like a quite painful undertaking, which will end
in some big heuristic algorithm.

I think, that getting good and meaningful errors for your language you
will need to do it by yourself. The result will be easier to maintain
and extend.

I don't quite understand why you're thinking that GHC is at all the
right tool. Well, I don't know exactly what you're really trying to do,
but have you already looked at LLVM (http://llvm.org/)?


Greetings,
Daniel

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


Re: [Haskell-cafe] Generating Haskell Code out of Haskell AST (GHC API)

2013-07-19 Thread Joachim Breitner
Hi,

Am Freitag, den 19.07.2013, 11:19 +0200 schrieb John Blackbox:

 The question about generating the code was only to have a debugging
 tool - to see if the generated AST is good - I wanted to generate the
 Haskell code only to check if its correct, but normally I would not do
 it, because it makes no sense to generate AST - code - AST (by GHC)
 again etc :)

it does make sense: ASCII (or today, Unicode text) is a much easier and
more stable interface than some ADT of a library. There is a good reason
why GHC generates llvm files and calls clang on them, instead of
generating the LLVM AST with some libllvm. Same for all the
pre-processors (happy, alex) – they all go through the serialized form.
It will be easier to plug components together, to inspect the
intermediate Haskell code or even modify it.

Of course if you need features not available via the command line, using
the API might be required. But for your own sake I suggest you avoid it
if possible.

Greetings,
Joachim

-- 
Joachim “nomeata” Breitner
  m...@joachim-breitner.de • http://www.joachim-breitner.de/
  Jabber: nome...@joachim-breitner.de  • GPG-Key: 0x4743206C
  Debian Developer: nome...@debian.org


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamic and equality

2013-07-19 Thread adam vogt
On Fri, Jul 19, 2013 at 5:19 AM, Jose A. Lopes jabolo...@google.com wrote:
 Hello,

 How to define equality for Data.Dynamic ?

Hi Jose,

You could try casting the values to different types that do have an
(==). You can treat the case where you have the types matching, but
didn't list that type beforehand differently.


eqTys a b
| Just a' - fromDynamic a, Just b' - fromDynamic b = a' == (b' :: Int)
| Just a' - fromDynamic a, Just b' - fromDynamic b = a' == (b' :: Integer)
| show a == show b = error equal types, but don't know if there's an (==)!
| otherwise = False


{-

 eqTys (toDyn 4) (toDyn 5)
False

 eqTys (toDyn 4) (toDyn 4)
True

 eqTys (toDyn 4) (toDyn 4.5)
False

 eqTys (toDyn 4.5) (toDyn 4.5)
*** Exception: equal types, but don't know if there's an (==)!

-}


--
Adam

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


[Haskell-cafe] List Monads and non-determinism

2013-07-19 Thread Matt Ford
Hi All,

I thought I'd have a go at destructing

[1,2] = \n - [3,4] = \m - return (n,m)

which results in [(1,3)(1,4),(2,3),(2,4)]

I started by putting brackets in

([1,2] = \n - [3,4]) = \m - return (n,m)

This immediately fails when evaluated: I expect it's something to do
with the n value now not being seen by the final return.

It seems to me that the return function is doing something more than
it's definition (return x = [x]).

If ignore the error introduced by the brackets I have and continue to
simplify I get.

[3,4,3,4] = \m - return (n,m)

Now this obviously won't work as there is no 'n' value.  So what's
happening here? Return seems to be doing way more work than lifting the
result to a list, how does Haskell know to do this?  Why's it not in the
function definition?  Are lists somehow a special case?

Any pointers appreciated.

Cheers,

-- 
Matt


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


Re: [Haskell-cafe] List Monads and non-determinism

2013-07-19 Thread Rogan Creswick
On Fri, Jul 19, 2013 at 3:23 PM, Matt Ford m...@dancingfrog.co.uk wrote:

 I started by putting brackets in

 ([1,2] = \n - [3,4]) = \m - return (n,m)

 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.


You're bracketing from the wrong end, which your intuition about n's
visibility hints at.  Try this as your first set of parens:

 [1,2] = (\n - [3,4] = \m - return (n,m))

--Rogan



 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).

 If ignore the error introduced by the brackets I have and continue to
 simplify I get.

 [3,4,3,4] = \m - return (n,m)

 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?

 Any pointers appreciated.

 Cheers,

 --
 Matt

 ___
 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] List Monads and non-determinism

2013-07-19 Thread Timon Gehr

On 07/20/2013 12:23 AM, Matt Ford wrote:

Hi All,

I thought I'd have a go at destructing

[1,2] = \n - [3,4] = \m - return (n,m)

which results in [(1,3)(1,4),(2,3),(2,4)]

I started by putting brackets in

([1,2] = \n - [3,4]) = \m - return (n,m)
...


This is not the same expression any more. See below for the correct 
bracketing.



This immediately fails when evaluated: I expect it's something to do
with the n value now not being seen by the final return.

It seems to me that the return function is doing something more than
it's definition (return x = [x]).

If ignore the error introduced by the brackets I have and continue to
simplify I get.

[3,4,3,4] = \m - return (n,m)

Now this obviously won't work as there is no 'n' value.  So what's
happening here? Return seems to be doing way more work than lifting the
result to a list, how does Haskell know to do this?  Why's it not in the
function definition?  Are lists somehow a special case?

Any pointers appreciated.
...



[1,2] = (\n - [3,4] = (\m - return (n,m)))

~*

((\n - [3,4] = (\m - return (n,m))) 1) ++ ((\n - [3,4] = (\m - 
return (n,m))) 2)


~*

([3,4] = (\m - return (1,m))) ++ ([3,4] = (\m - return (2,m)))

~*

((\m - return (1,m)) 3 ++ (\m - return (1,m)) 4) ++ ((\m - return 
(2,m)) 3 ++ (\m - return (2,m)) 4)


~*

return (1,3) ++ return (1,4) ++ return (2,3) ++ return (2,4)

~*

[(1,3)] ++ [(1,4)] ++ [(2,3)] ++ [(2,4)]

~*

[(1,3),(1,4),(2,3),(2,4)]

Where the definition return x = [x] has been applied in the second-last 
step.







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


Re: [Haskell-cafe] List Monads and non-determinism

2013-07-19 Thread Matt Ford
Hi,

Thanks for the help.

I thought = was left associative?  It seems to be in the examples from Learn 
You A Haskell.

I tried to use the associative law to bracket from the right but it didn't like 
that either...

[1,2] = (\x - (\n - [3,4])) x  = \m - return (n,m))

Any thoughts?

Matt 

On 19 Jul 2013, at 23:35, Rogan Creswick cresw...@gmail.com wrote:

 On Fri, Jul 19, 2013 at 3:23 PM, Matt Ford m...@dancingfrog.co.uk wrote:
 I started by putting brackets in
 
 ([1,2] = \n - [3,4]) = \m - return (n,m)
 
 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.
 
 You're bracketing from the wrong end, which your intuition about n's 
 visibility hints at.  Try this as your first set of parens:
 
  [1,2] = (\n - [3,4] = \m - return (n,m))
 
 --Rogan
  
 
 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).
 
 If ignore the error introduced by the brackets I have and continue to
 simplify I get.
 
 [3,4,3,4] = \m - return (n,m)
 
 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?
 
 Any pointers appreciated.
 
 Cheers,
 
 --
 Matt
 
 ___
 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] List Monads and non-determinism

2013-07-19 Thread Rogan Creswick
On Fri, Jul 19, 2013 at 3:58 PM, Matt Ford m...@dancingfrog.co.uk wrote:

 Hi,

 Thanks for the help.

 I thought = was left associative?  It seems to be in the examples from
 Learn You A Haskell.

 I tried to use the associative law to bracket from the right but it didn't
 like that either...

 [1,2] = (\x - (\n - [3,4])) x  = \m - return (n,m))


I think the issue is that you need to first take into account the lambdas
*then* use what you know about the properties of (=).

I found this stackoverflow answer helpful (
http://stackoverflow.com/a/11237469)

The rule for lambdas is pretty simple: the body of the lambda extends as
far to the right as possible without hitting an unbalanced parenthesis.

 So, the first lambda runs to the end of the expression:

[1,2] = (\n - [3,4] = \m - return (n,m))

Now, there is still a lambda nested inside the first lambda: \m - return
(n,m)

[1,2] = (\n - [3,4] = (\m - return (n,m)))

You violated the implied grouping that these new parentheses make explicit
when you tried to apply the associative law above.

Timon's post continues from this point to show the full deconstruction.

--Rogan


 Any thoughts?

 Matt

 On 19 Jul 2013, at 23:35, Rogan Creswick cresw...@gmail.com wrote:

 On Fri, Jul 19, 2013 at 3:23 PM, Matt Ford m...@dancingfrog.co.uk wrote:

 I started by putting brackets in

 ([1,2] = \n - [3,4]) = \m - return (n,m)

 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.


 You're bracketing from the wrong end, which your intuition about n's
 visibility hints at.  Try this as your first set of parens:

  [1,2] = (\n - [3,4] = \m - return (n,m))

 --Rogan



 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).

 If ignore the error introduced by the brackets I have and continue to
 simplify I get.

 [3,4,3,4] = \m - return (n,m)

 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?

 Any pointers appreciated.

 Cheers,

 --
 Matt

 ___
 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] List Monads and non-determinism

2013-07-19 Thread Chris Wong
 I thought = was left associative?  It seems to be in the examples from
 Learn You A Haskell.

It is. But lambdas are parsed using the maximal munch rule, so they
extend *as far to the right as possible*.

So

\x - x * 2 + 1

would be parsed as

\x - (x * 2 + 1)  -- right

not

(\x - x) * 2 + 1  -- wrong

which is obviously incorrect.

I believe C uses a similar rule for funny expressions like `x+++y`
(using maximal munch: `(x++) + y`).


 I tried to use the associative law to bracket from the right but it didn't
 like that either...

 [1,2] = (\x - (\n - [3,4])) x  = \m - return (n,m))

 Any thoughts?

 Matt

 On 19 Jul 2013, at 23:35, Rogan Creswick cresw...@gmail.com wrote:

 On Fri, Jul 19, 2013 at 3:23 PM, Matt Ford m...@dancingfrog.co.uk wrote:

 I started by putting brackets in

 ([1,2] = \n - [3,4]) = \m - return (n,m)

 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.


 You're bracketing from the wrong end, which your intuition about n's
 visibility hints at.  Try this as your first set of parens:

  [1,2] = (\n - [3,4] = \m - return (n,m))

 --Rogan



 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).

 If ignore the error introduced by the brackets I have and continue to
 simplify I get.

 [3,4,3,4] = \m - return (n,m)

 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?

 Any pointers appreciated.

 Cheers,

 --
 Matt

 ___
 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




--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] List Monads and non-determinism

2013-07-19 Thread Timon Gehr

On 07/20/2013 12:58 AM, Matt Ford wrote:

Hi,

Thanks for the help.

I thought = was left associative?  It seems to be in the examples from
Learn You A Haskell.
...


Yes, = is left-associative. The associativity of = is not relevant 
for your example because no two = operations actually occur next to 
each other. The second = is part of the lambda occurring as the second 
argument to the first =. Lambdas bind 'the rest of the expression'.


[1,2] = \n - [3,4] = \m - return (n,m)

is equivalent to:

let a = [1,2]
b = (\n - [3,4] = \m - return (n,m))
in a = b




I tried to use the associative law to bracket from the right but it
didn't like that either...

[1,2] = (\x - (\n - [3,4])) x  = \m - return (n,m))

Any thoughts?
...


Where does that 'x' come from?


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


Re: [Haskell-cafe] Wrapping all fields of a data type in e.g. Maybe

2013-07-19 Thread Michael Orlitzky
On 07/16/2013 04:57 PM, Michael Orlitzky wrote:
 
 This all works great, except that when there's 20 or so options, I
 duplicate a ton of code in the definition of OptionalCfg. Is there some
 pre-existing solution that will let me take a Cfg and create a new type
 with Cfg's fields wrapped in Maybe?
 

For posterity, I report failure =)

If I parameterize the Configuration type by a functor, it breaks the
DeriveDataTypeable magic in cmdargs. The resulting manual definitions
along with the lenses to look inside the Identity functor well exceed
the duplicated code from OptionalCfg.

Combining the option parsing and config file parsing increases the
amount of code in the command-line parser by roughly an equal amount,
but in my opinion a worse consequence is that it conflates two unrelated
procedures. I very much like this:

  rc_cfg  - from_rc
  cmd_cfg - apply_args
  let opt_config = rc_cfg  cmd_cfg
  ...

All things considered the duplicated data structure seems like the least
of three evils.


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


Re: [Haskell-cafe] Dynamic and equality

2013-07-19 Thread Carter Schonwald
the tricky part then is to add support for other types.

another approach to existentially package type classes with the data type!

eg
data HasEq  = forall a . HasEq ( Eq a = a)
or its siblinng
data HasEq a = Haseq (Eq a = a )

note this requires more planning in how you structure your program, but is
a much more pleasant approach than using dynamic when you can get it to
suite your application needs.

note its also late, so I've not type checked these examples ;)

-Carter



On Fri, Jul 19, 2013 at 12:54 PM, adam vogt vogt.a...@gmail.com wrote:

 On Fri, Jul 19, 2013 at 5:19 AM, Jose A. Lopes jabolo...@google.com
 wrote:
  Hello,
 
  How to define equality for Data.Dynamic ?

 Hi Jose,

 You could try casting the values to different types that do have an
 (==). You can treat the case where you have the types matching, but
 didn't list that type beforehand differently.


 eqTys a b
 | Just a' - fromDynamic a, Just b' - fromDynamic b = a' == (b' ::
 Int)
 | Just a' - fromDynamic a, Just b' - fromDynamic b = a' == (b' ::
 Integer)
 | show a == show b = error equal types, but don't know if there's an
 (==)!
 | otherwise = False


 {-

  eqTys (toDyn 4) (toDyn 5)
 False

  eqTys (toDyn 4) (toDyn 4)
 True

  eqTys (toDyn 4) (toDyn 4.5)
 False

  eqTys (toDyn 4.5) (toDyn 4.5)
 *** Exception: equal types, but don't know if there's an (==)!

 -}


 --
 Adam

 ___
 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