Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Ben Millwood
On Fri, Jun 11, 2010 at 12:46 AM, Felipe Lessa felipe.le...@gmail.com wrote:

  eqTypeable :: (Typeable a, Eq a, Typeable b, Eq b) = a - b - Bool
  eqTypeable x y = case cast y of
                     Just y' - x == y'
                     Nothing - False


...or indeed:

eqTypeable x y = cast x == Just y
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Ozgur Akgun
I don't know whether its a good name or not (the ===), but I have the
following in a generic utilities file I have, and I use it every now and
then.

(===) :: (Typeable a, Typeable b, Eq b) = a - b - Bool
(===) x y = cast x == Just y

(Notice you don't need Eq a in the context)

On 11 June 2010 12:51, Ben Millwood hask...@benmachine.co.uk wrote:

 On Fri, Jun 11, 2010 at 12:46 AM, Felipe Lessa felipe.le...@gmail.com
 wrote:
 
   eqTypeable :: (Typeable a, Eq a, Typeable b, Eq b) = a - b - Bool
   eqTypeable x y = case cast y of
  Just y' - x == y'
  Nothing - False
 

 ...or indeed:

 eqTypeable x y = cast x == Just y
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Dupont Corentin
Thanks all, it works fine (see below).

I lamentably try to make the same for show:
 showTypeable :: (Typeable a) = a - String
 showTypeable x = case cast x of
  Just x' - show x'
  Nothing - 

Because it really upsets me to add this show constraints to the Equ
constructor ;)
what if i want to make an Obs instance with non showable elements, with no
intention to show it of course?

Corentin

 instance Typeable1 Obs where
typeOf1 _ = mkTyConApp (mkTyCon Obs) []

 (===) :: (Typeable a, Typeable b, Eq b) = a - b - Bool
 (===) x y = cast x == Just y


 data Obs a where
 Player   :: Obs Player
 Official :: Obs Bool
 Equ  :: (Eq a, Show a, Typeable a) = Obs a - Obs a - Obs Bool
 Plus :: (Num a) = Obs a - Obs a - Obs a
 Time :: (Num a) = Obs a - Obs a - Obs a
 Minus:: (Num a) = Obs a - Obs a - Obs a
 And  :: Obs Bool - Obs Bool - Obs Bool
 Or   :: Obs Bool - Obs Bool - Obs Bool
 Not  :: Obs Bool - Obs Bool
 Konst:: (Show a, Eq a) = a - Obs a



 instance Show t = Show (Obs t) where
 show Player  = Player
 show Official= Official
 show (Equ a b)   = (show a) ++  Eq  ++ (show b)
 show (Plus a b)  = (show a) ++  Plus  ++ (show b)
 show (Minus a b) = (show a) ++  Minus  ++ (show b)
 show (Time a b)  = (show a) ++  Time  ++ (show b)
 show (Konst a)   =  (Konst  ++ (show a) ++ )
 show (And a b)   = (show a) ++  And  ++ (show b)
 show (Or a b)= (show a) ++  Or  ++ (show b)
 show (Not a) =  (Not  ++ (show a) ++ )


 instance Eq t = Eq (Obs t) where
 Player == Player   = True
 Official == Official   = True
 Equ a b == Equ c d = (a,b) === (c,d)
 Plus a b == Plus c d   = (a == c)  (b == d)
 Minus a b == Minus c d = (a == c)  (b == d)
 Time a b == Time c d   = (a == c)  (b == d)
 And a b == And c d = (a == c)  (b == d)
 Or a b == Or c d   = (a == c)  (b == d)
 Not a == Not b = (a == b)
 Konst a == Konst b = a == b
 _ == _ = False
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Felipe Lessa
On Sat, Jun 12, 2010 at 12:13:14AM +0200, Dupont Corentin wrote:
 Thanks all, it works fine (see below).

 I lamentably try to make the same for show:
  showTypeable :: (Typeable a) = a - String
  showTypeable x = case cast x of
   Just x' - show x'
   Nothing - 

 Because it really upsets me to add this show constraints to the Equ
 constructor ;)
 what if i want to make an Obs instance with non showable elements, with no
 intention to show it of course?

Ad hoc solution:

  class MaybeShow a where
maybeShow :: a - Maybe String

  instance Show a = MaybeShow a where
maybeShow = Just . show

  instance MaybeShow a where
maybeShow = Nothing

  data MyData where
Something :: MaybeShow a = a - MyData

  instance MaybeShow MyData where
maybeShow (Something x) =
  fmap (\s - Something ( ++ s ++ )) (maybeShow x)

Hahahaha :).  Try to guess without using GHC/GHCi:

  1) Which extensions are required to make the code compile.

  2) After compiled, if it works as intended or not.

Cheers,

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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-10 Thread Dupont Corentin
On Thu, Jun 10, 2010 at 11:14 PM, Daniel Fischer
daniel.is.fisc...@web.dewrote:

 On Thursday 10 June 2010 22:01:38, Dupont Corentin wrote:
  Hello Maciej,
  i tried this out, but it didn't worked.
 
  Daniel,
 
  I added a (Show a) constraint to Equal:
   data Obs a where
   Player :: Obs Integer
   Turn :: Obs Integer
   Official :: Obs Bool
   Equ :: (Show a, Eq a) = Obs a - Obs a - Obs Bool
 
  --woops!!
 
   Plus :: (Num a) = Obs a - Obs a - Obs a
   Time :: (Num a) = Obs a - Obs a - Obs a
   Minus :: (Num a) = Obs a - Obs a - Obs a
   Konst :: a - Obs a
   And :: Obs Bool - Obs Bool - Obs Bool
   Or :: Obs Bool - Obs Bool - Obs Bool
 
  It works for the Show instance, but not Eq.
  By the way, shouldn't the Show constraint be on the instance and not on
  the datatype declaration?

 Can't be here, because of
   Equ :: Obs a - Obs a - Obs Bool

 You forget the parameter a, and you can't recover it in the instance
 declaration. So you have to provide the Show instance for a on
 construction, i.e. put the constraint on the data constructor.


Anyway, is my Obs construction revelant at all? What i want to do is to
provide an EDSL to the user to test things about the state of the game (for
the Nomic game i'm making). Obs will be then embedded in another EDSL to
construct Nomic's rules.



  I'd prefer to keep the datatype as generic as possible...
 
  There is really no way to make my Obs datatype an instance of Eq and
  Show??

 Show can work (should with the constraint on Equ), Eq is hairy.

 instance Show t = Show (Obs t) where
 show (Equ a b) = show a ++  `Equal`  ++ show b
show (Plus a b) = ...
show (Konst x) = Konst  ++ show x
...

 For an Eq instance, you have the problem that

 Equ (Konst True) (Konst False)
 and
 Equ Player Turn

 both have the type Obs Bool, but have been constructed from different
 types, so you can't compare (Konst True) and Player.
 I don't see a nice way to work around that.


These is a dirty way: compare the string representation of the rules. They
should be unique.

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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-10 Thread Dupont Corentin
Hello Maciej,
i tried this out, but it didn't worked.

Daniel,
I added a (Show a) constraint to Equal:

 data Obs a where
 Player :: Obs Integer
 Turn :: Obs Integer
 Official :: Obs Bool
 Equ :: (Show a, Eq a) = Obs a - Obs a - Obs Bool
--woops!!
 Plus :: (Num a) = Obs a - Obs a - Obs a
 Time :: (Num a) = Obs a - Obs a - Obs a
 Minus :: (Num a) = Obs a - Obs a - Obs a
 Konst :: a - Obs a
 And :: Obs Bool - Obs Bool - Obs Bool
 Or :: Obs Bool - Obs Bool - Obs Bool


It works for the Show instance, but not Eq.
By the way, shouldn't the Show constraint be on the instance and not on the
datatype declaration?
I'd prefer to keep the datatype as generic as possible...

There is really no way to make my Obs datatype an instance of Eq and Show??

I searched around a way to add type information on the pattern match like:

 instance Show t = Show (Obs t) where
 show (Equal (a::Obs t) (b::Obs t)) = (show a) ++  Equal  ++ (show b)
 show (Plus a b) = (show a) ++  Plus  ++ (show b)


But it doesn't work.

thanks for your help,
Corentin



On Thu, Jun 10, 2010 at 2:47 AM, Maciej Piechotka uzytkown...@gmail.comwrote:

 On Wed, 2010-06-09 at 22:28 +0200, Dupont Corentin wrote:
  Thanks for your response.
 
  How would you do it? I design this GATD for a game i'm making:
 
   data Obs a where
   Player :: Obs Integer
   Turn :: Obs Integer
   Official :: Obs Bool
   Equ :: Obs a - Obs a - Obs Bool   --woops!!
   Plus :: (Num a) = Obs a - Obs a - Obs a
   Time :: (Num a) = Obs a - Obs a - Obs a
   Minus :: (Num a) = Obs a - Obs a - Obs a
   Konst :: a - Obs a

 Actually woops is here. Make it for example

Const :: (Show a, Eq a, ...) = a - Obs a

   And :: Obs Bool - Obs Bool - Obs Bool
   Or :: Obs Bool - Obs Bool - Obs Bool
 
  For example I can design an Observable like that:
 
  myObs = Player `Equ` (Konst 1) `And` Official
 
  These Observables will then be processed during gameplay.
 
  I would like to be able to do in ghci:
 
   show myObs
  Player `Equ` (Konst 1) `And` Official
 
  and:
myObs == myObs
  True
 

 Regards


 ___
 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] Re: GATD and pattern matching

2010-06-10 Thread Daniel Fischer
On Thursday 10 June 2010 22:01:38, Dupont Corentin wrote:
 Hello Maciej,
 i tried this out, but it didn't worked.

 Daniel,

 I added a (Show a) constraint to Equal:
  data Obs a where
  Player :: Obs Integer
  Turn :: Obs Integer
  Official :: Obs Bool
  Equ :: (Show a, Eq a) = Obs a - Obs a - Obs Bool

 --woops!!

  Plus :: (Num a) = Obs a - Obs a - Obs a
  Time :: (Num a) = Obs a - Obs a - Obs a
  Minus :: (Num a) = Obs a - Obs a - Obs a
  Konst :: a - Obs a
  And :: Obs Bool - Obs Bool - Obs Bool
  Or :: Obs Bool - Obs Bool - Obs Bool

 It works for the Show instance, but not Eq.
 By the way, shouldn't the Show constraint be on the instance and not on
 the datatype declaration?

Can't be here, because of 
  Equ :: Obs a - Obs a - Obs Bool

You forget the parameter a, and you can't recover it in the instance 
declaration. So you have to provide the Show instance for a on 
construction, i.e. put the constraint on the data constructor.

 I'd prefer to keep the datatype as generic as possible...

 There is really no way to make my Obs datatype an instance of Eq and
 Show??

Show can work (should with the constraint on Equ), Eq is hairy.

instance Show t = Show (Obs t) where
show (Equ a b) = show a ++  `Equal`  ++ show b
show (Plus a b) = ...
show (Konst x) = Konst  ++ show x
...

For an Eq instance, you have the problem that

Equ (Konst True) (Konst False)
and
Equ Player Turn

both have the type Obs Bool, but have been constructed from different 
types, so you can't compare (Konst True) and Player.
I don't see a nice way to work around that.


 I searched around a way to add type information on the pattern match 
like:
  instance Show t = Show (Obs t) where
  show (Equal (a::Obs t) (b::Obs t)) = (show a) ++  Equal  ++
  (show b) show (Plus a b) = (show a) ++  Plus  ++ (show b)

 But it doesn't work.

 thanks for your help,
 Corentin

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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-10 Thread Felipe Lessa
On Thu, Jun 10, 2010 at 11:14:42PM +0200, Daniel Fischer wrote:
 Show can work (should with the constraint on Equ), Eq is hairy.

 instance Show t = Show (Obs t) where
 show (Equ a b) = show a ++  `Equal`  ++ show b
 show (Plus a b) = ...
 show (Konst x) = Konst  ++ show x
 ...

 For an Eq instance, you have the problem that

 Equ (Konst True) (Konst False)
 and
 Equ Player Turn

 both have the type Obs Bool, but have been constructed from different
 types, so you can't compare (Konst True) and Player.
 I don't see a nice way to work around that.

I didn't test, but something like this could work:

  Equ :: (Show a, Eq a, Typeable a) = Obs a - Obs a - Obs Bool

  (Equ a b) == (Equ c d) = eqTypeable (a,b) (c,d)

  eqTypeable :: (Typeable a, Eq a, Typeable b, Eq b) = a - b - Bool
  eqTypeable x y = case cast y of
 Just y' - x == y'
 Nothing - False

Maybe not ;).

Cheers,

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


[Haskell-cafe] Re: GATD and pattern matching

2010-06-09 Thread Maciej Piechotka
On Wed, 2010-06-09 at 22:28 +0200, Dupont Corentin wrote:
 Thanks for your response.
 
 How would you do it? I design this GATD for a game i'm making:
 
  data Obs a where 
  Player :: Obs Integer 
  Turn :: Obs Integer
  Official :: Obs Bool 
  Equ :: Obs a - Obs a - Obs Bool   --woops!!
  Plus :: (Num a) = Obs a - Obs a - Obs a 
  Time :: (Num a) = Obs a - Obs a - Obs a 
  Minus :: (Num a) = Obs a - Obs a - Obs a 
  Konst :: a - Obs a 

Actually woops is here. Make it for example

Const :: (Show a, Eq a, ...) = a - Obs a

  And :: Obs Bool - Obs Bool - Obs Bool 
  Or :: Obs Bool - Obs Bool - Obs Bool
 
 For example I can design an Observable like that:
 
 myObs = Player `Equ` (Konst 1) `And` Official
 
 These Observables will then be processed during gameplay.
 
 I would like to be able to do in ghci:
 
  show myObs
 Player `Equ` (Konst 1) `And` Official
 
 and:
   myObs == myObs
 True
 

Regards



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