Re: [Haskell-cafe] Parsing different types, same typeclass

2012-11-18 Thread Stephen Tetley
With existentials an extesible version might look like this:

 {-# LANGUAGE ExistentialQuantification #-}
 {-# LANGUAGE ScopedTypeVariables #-}


... class Action and datatypes A and B the same as before ...


 -- some new ones...

 data C = C Int
  deriving (Read, Show)


 instance Action C where
  run (C n) = n


 data D = D Int
  deriving (Read, Show)

 instance Action D where
  run (D n) = n


The important one:

 data PolyA = forall a. Action a = PolyA a


 parseAction :: String - PolyA
 parseAction str
  | (A  `isPrefixOf` str = PolyA $ (read :: String - A) str
  | (B  `isPrefixOf` str = PolyA $ (read :: String - B) str

  -- can add new cases
  | (C  `isPrefixOf` str = PolyA $ (read :: String - C) str
  | (D  `isPrefixOf` str = PolyA $ (read :: String - D) str


This is extensible to some degree as you can add new cases of
different types, but all you can do with these different types is
run them to make an Int, so it is equivalent to the second version I
gave previously:

 parseAction :: String - Int
 parseAction str
 | (A  `isPrefixOf` str = run $ (read str :: A)
 | (B  `isPrefixOf` str = run $ (read str :: B)
 | (C  `isPrefixOf` str = run $ (read str :: C)
 | (D  `isPrefixOf` str = run $ (read str :: D)

i.e instead of using an existential type to hold something polymorphic
that can be run to produce an Int, just call run at the point of use
making an Int.

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


Re: [Haskell-cafe] Parsing different types, same typeclass

2012-11-18 Thread Jose A. Lopes

Hey Chris,

Thanks for you reply!

So the thing is: I actually had an algebraic data type Action with
several constructors, one for each Action. And I was deriving
Read so there was no problem there.

However, I want to be able to add and remove Actions more easily.
That is why I transformed the algebraic data type into a typeclass.
Similarly, if you think about Object Oriented programming, I want
the flexibility of subclassing, where new subclasses can be added
without a problem. The fact that parseAction only works on a finite
number of Actions is not problematic for now!

So, I would really appreciate your help in overcoming this problem!

Best regards,
José

On 18-11-2012 03:08, Chris Wong wrote:

Hello José,


So, I have a typeclass Action which defines method run:

class Action a where
 run :: a - Int

(snipped)

Now, I want to parse either A or B from a String.
I was thinking about something like this...

parseAction :: (Action a, Read a) = String - a
parseAction str
 | (A  `isPrefixOf` str = (read :: String - A) str
 | (B  `isPrefixOf` str = (read :: String - B) str

The problem is that when calling parseAction I get ambiguous type
constraints. How to implement a parse function for two distinct
types that share the same typeclass Action. Because after calling
parseAction I don't whether A or B was returned: I only care
that they are Action instances so I can call run.

The problem with your current type:

 (Action a, Read a) = String - a

is that it actually means:

 For any type that implements Action and Read, I can convert a
string to that type.

This is wrong because if a user of your module added another type C,
your function wouldn't be able to handle it -- it only knows about A
and B. That is what GHC is trying to tell you.

How you can solve this problem depends on what you're trying to do. If
there is a finite number of actions, you can merge them into a single
type and remove the type class altogether:

 data Action = A Int | B Int
 deriving (Read, Show)

 run :: Action - Int
 run (A x) = x
 run (B x) = x

 parse :: String - Action
 parse = read

If you have a possibly unlimited number of possible actions, there are
many approaches to this -- including, as Stephen said, existential
types. However, it's hard to decide on a proper solution without
knowing what you're actually trying to do.

Chris


Best regards,
José

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


--
José António Branquinho de Oliveira Lopes
Instituto Superior Técnico
Technical University of Lisbon


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


Re: [Haskell-cafe] Parsing different types, same typeclass

2012-11-18 Thread Jose A. Lopes

Thanks Stephen. I will try this!

On 18-11-2012 17:56, Stephen Tetley wrote:

With existentials an extesible version might look like this:


{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}


... class Action and datatypes A and B the same as before ...



-- some new ones...
data C = C Int
  deriving (Read, Show)



instance Action C where
  run (C n) = n



data D = D Int
  deriving (Read, Show)
instance Action D where
  run (D n) = n


The important one:


data PolyA = forall a. Action a = PolyA a



parseAction :: String - PolyA
parseAction str
  | (A  `isPrefixOf` str = PolyA $ (read :: String - A) str
  | (B  `isPrefixOf` str = PolyA $ (read :: String - B) str

  -- can add new cases
  | (C  `isPrefixOf` str = PolyA $ (read :: String - C) str
  | (D  `isPrefixOf` str = PolyA $ (read :: String - D) str


This is extensible to some degree as you can add new cases of
different types, but all you can do with these different types is
run them to make an Int, so it is equivalent to the second version I
gave previously:


parseAction :: String - Int
parseAction str
 | (A  `isPrefixOf` str = run $ (read str :: A)
 | (B  `isPrefixOf` str = run $ (read str :: B)
 | (C  `isPrefixOf` str = run $ (read str :: C)
 | (D  `isPrefixOf` str = run $ (read str :: D)

i.e instead of using an existential type to hold something polymorphic
that can be run to produce an Int, just call run at the point of use
making an Int.


--
José António Branquinho de Oliveira Lopes
Instituto Superior Técnico
Technical University of Lisbon


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


Re: [Haskell-cafe] Parsing different types, same typeclass

2012-11-18 Thread Jose A. Lopes

Thanks Stephen, that worked out just fine!

On 18-11-2012 18:23, Jose A. Lopes wrote:

Thanks Stephen. I will try this!

On 18-11-2012 17:56, Stephen Tetley wrote:

With existentials an extesible version might look like this:


{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}


... class Action and datatypes A and B the same as before ...



-- some new ones...
data C = C Int
  deriving (Read, Show)



instance Action C where
  run (C n) = n



data D = D Int
  deriving (Read, Show)
instance Action D where
  run (D n) = n


The important one:


data PolyA = forall a. Action a = PolyA a



parseAction :: String - PolyA
parseAction str
  | (A  `isPrefixOf` str = PolyA $ (read :: String - A) str
  | (B  `isPrefixOf` str = PolyA $ (read :: String - B) str

  -- can add new cases
  | (C  `isPrefixOf` str = PolyA $ (read :: String - C) str
  | (D  `isPrefixOf` str = PolyA $ (read :: String - D) str


This is extensible to some degree as you can add new cases of
different types, but all you can do with these different types is
run them to make an Int, so it is equivalent to the second version I
gave previously:


parseAction :: String - Int
parseAction str
 | (A  `isPrefixOf` str = run $ (read str :: A)
 | (B  `isPrefixOf` str = run $ (read str :: B)
 | (C  `isPrefixOf` str = run $ (read str :: C)
 | (D  `isPrefixOf` str = run $ (read str :: D)

i.e instead of using an existential type to hold something polymorphic
that can be run to produce an Int, just call run at the point of use
making an Int.




--
José António Branquinho de Oliveira Lopes
Instituto Superior Técnico
Technical University of Lisbon


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


[Haskell-cafe] Parsing different types, same typeclass

2012-11-17 Thread José Lopes

Hello everyone,

I was wondering if you could help me!

So, I have a typeclass Action which defines method run:

class Action a where
run :: a - Int

and two data types that are instances of this typeclass:

data A = A Int
deriving (Read, Show)

instance Action A where
run (A n) = n


data B = B Int
deriving (Read, Show)

instance Action B where
run (B n) = n

Now, I want to parse either A or B from a String.
I was thinking about something like this...

parseAction :: (Action a, Read a) = String - a
parseAction str
| (A  `isPrefixOf` str = (read :: String - A) str
| (B  `isPrefixOf` str = (read :: String - B) str

The problem is that when calling parseAction I get ambiguous type
constraints. How to implement a parse function for two distinct
types that share the same typeclass Action. Because after calling
parseAction I don't whether A or B was returned: I only care
that they are Action instances so I can call run.

Best regards,
José

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


Re: [Haskell-cafe] Parsing different types, same typeclass

2012-11-17 Thread Stephen Tetley
Being concrete, all you can do is:

parseAction :: String - Either A B
parseAction str
| (A  `isPrefixOf` str = Left $ read str
| (B  `isPrefixOf` str = Right $ read str


parseAction :: String - Int
parseAction str
| (A  `isPrefixOf` str = run $ (read str :: A)
| (B  `isPrefixOf` str = run $ (read str :: B)

As you can't return a polymorphic /a/ when you have typed the cases to A or B.

Being less concrete, no doubt you can use existentials, but at this
point I'd recommend you re-evaluate what you are trying to do.

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


Re: [Haskell-cafe] Parsing different types, same typeclass

2012-11-17 Thread José A. Lopes

Hey Stephen,

Thank you for the reply!

Can you elaborate on how I can use existentials?
I always up for learning new (Haskell) stuff :)

Cheers,
José

On 18-11-2012 00:19, Stephen Tetley wrote:

Being concrete, all you can do is:

parseAction :: String - Either A B
parseAction str
 | (A  `isPrefixOf` str = Left $ read str
 | (B  `isPrefixOf` str = Right $ read str


parseAction :: String - Int
parseAction str
 | (A  `isPrefixOf` str = run $ (read str :: A)
 | (B  `isPrefixOf` str = run $ (read str :: B)

As you can't return a polymorphic /a/ when you have typed the cases to A or B.

Being less concrete, no doubt you can use existentials, but at this
point I'd recommend you re-evaluate what you are trying to do.


--
José António Branquinho de Oliveira Lopes
Instituto Superior Técnico
Technical University of Lisbon


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


Re: [Haskell-cafe] Parsing different types, same typeclass

2012-11-17 Thread Chris Wong
Hello José,

 So, I have a typeclass Action which defines method run:

 class Action a where
 run :: a - Int

 (snipped)

 Now, I want to parse either A or B from a String.
 I was thinking about something like this...

 parseAction :: (Action a, Read a) = String - a
 parseAction str
 | (A  `isPrefixOf` str = (read :: String - A) str
 | (B  `isPrefixOf` str = (read :: String - B) str

 The problem is that when calling parseAction I get ambiguous type
 constraints. How to implement a parse function for two distinct
 types that share the same typeclass Action. Because after calling
 parseAction I don't whether A or B was returned: I only care
 that they are Action instances so I can call run.

The problem with your current type:

(Action a, Read a) = String - a

is that it actually means:

For any type that implements Action and Read, I can convert a
string to that type.

This is wrong because if a user of your module added another type C,
your function wouldn't be able to handle it -- it only knows about A
and B. That is what GHC is trying to tell you.

How you can solve this problem depends on what you're trying to do. If
there is a finite number of actions, you can merge them into a single
type and remove the type class altogether:

data Action = A Int | B Int
deriving (Read, Show)

run :: Action - Int
run (A x) = x
run (B x) = x

parse :: String - Action
parse = read

If you have a possibly unlimited number of possible actions, there are
many approaches to this -- including, as Stephen said, existential
types. However, it's hard to decide on a proper solution without
knowing what you're actually trying to do.

Chris

 Best regards,
 José

 ___
 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