Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Question on data/type (Phillip Pirrip)
   2. Re:  Functor question. (Brent Yorgey)
   3. Re:  Question on data/type (i?fai)
   4. Re:  Question on data/type (Brent Yorgey)
   5.  Functor question  (Matthew Wong)
   6.  Questions on data/type (Matthew Wong)
   7. Re:  Functor question (Jason Dusek)
   8. Re:  Questions on data/type (Jason Dusek)
   9. Re:  Question on data/type (David Virebayre)
  10. Re:  Question on data/type (Felipe Lessa)


----------------------------------------------------------------------

Message: 1
Date: Mon, 16 Nov 2009 00:33:51 -0500
From: Phillip Pirrip <ppir...@gmail.com>
Subject: [Haskell-beginners] Question on data/type
To: beginners@haskell.org
Message-ID: <7dc11d2c-abde-4956-adcf-5a5c9ea24...@gmail.com>
Content-Type: text/plain; charset=us-ascii

Hi,

I have the following data defined.

data TypeCon a = ValConA a | ValConB [a] | ValConC [[a]]

So I can use functions with type like  (a->a->a) -> TypeCon a -> TypeCon a -> 
TypeCon a
for all 3 value types, and I think is easier to define one single typeclass for 
(+), (*) etc.

If I want to express the following idea (the following won't compiler):

data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]

Is this even a good idea?  If so how could I proceed?  The closest thing I can 
get to compiler is like this:

data TypeCon a = ValConA a | ValConB [TypeCon a] 

Which is a nightmare when I try to manipulate anything in this structure.  The 
alternative I guess is to use 3 different type constructors,

data TypeConA a = ValConA a
data TypeConB a = ValConB [ValConA a]
data TypeConC a = ValConC [ValConB a]

but then I can't use one signal typeclass for (+) etc.  Am I correct?

thx,

//pip


------------------------------

Message: 2
Date: Mon, 16 Nov 2009 06:47:43 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Functor question.
To: beginners@haskell.org
Message-ID: <20091116114743.ga7...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sun, Nov 15, 2009 at 08:07:36PM -0800, Alexander Dunlap wrote:
> 
> In general, people recommend against using constriants on datatypes,
> recommending instead to put those constraints on the functions that
> operate on the datatypes. I'm not quite sure why that is, though.

It is because adding a constraint to a datatype definition only puts a
constraint on the *constructor*---in particular, you don't get any
constraints when pattern-matching, and you have to put the constraints
on functions that operate on the datatype anyway.

-Brent


------------------------------

Message: 3
Date: Mon, 16 Nov 2009 11:57:45 -0500
From: i?fai <iae...@me.com>
Subject: Re: [Haskell-beginners] Question on data/type
To: Phillip Pirrip <ppir...@gmail.com>
Cc: Beginners@haskell.org
Message-ID: <074ddf16-e80a-4f22-8c36-bb2527af0...@me.com>
Content-Type: text/plain; charset=iso-8859-1

I will try to help with my limited knowledge and what I believe to be going on.

When you try to compile:

> data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]

You get this: 

Not in scope: type constructor or class `ValConA'
Not in scope: type constructor or class `ValConB'

What you have here is a type constructor TypeCon and a data constructor 
ValConA, ValConB, ValConC. When you are constructing your different data 
constructors (such as ValConA) you have to give it type constructors, or 
substitutes like a. You can do this:

data TypeCon a = ValConA a | ValConB [TypeCon a]

Regards,
iƦfai.


On 2009-11-16, at 12:33 AM, Phillip Pirrip wrote:

> Hi,
> 
> I have the following data defined.
> 
> data TypeCon a = ValConA a | ValConB [a] | ValConC [[a]]
> 
> So I can use functions with type like  (a->a->a) -> TypeCon a -> TypeCon a -> 
> TypeCon a
> for all 3 value types, and I think is easier to define one single typeclass 
> for (+), (*) etc.
> 
> If I want to express the following idea (the following won't compiler):
> 
> data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]
> 
> Is this even a good idea?  If so how could I proceed?  The closest thing I 
> can get to compiler is like this:
> 
> data TypeCon a = ValConA a | ValConB [TypeCon a] 
> 
> Which is a nightmare when I try to manipulate anything in this structure.  
> The alternative I guess is to use 3 different type constructors,
> 
> data TypeConA a = ValConA a
> data TypeConB a = ValConB [ValConA a]
> data TypeConC a = ValConC [ValConB a]
> 
> but then I can't use one signal typeclass for (+) etc.  Am I correct?
> 
> thx,
> 
> //pip
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



------------------------------

Message: 4
Date: Mon, 16 Nov 2009 13:17:19 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Question on data/type
To: beginners@haskell.org
Message-ID: <20091116181719.ga10...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Nov 16, 2009 at 12:33:51AM -0500, Phillip Pirrip wrote:
> Hi,
> 
> I have the following data defined.
> 
> data TypeCon a = ValConA a | ValConB [a] | ValConC [[a]]
> 
> So I can use functions with type like  (a->a->a) -> TypeCon a -> TypeCon a -> 
> TypeCon a
> for all 3 value types, and I think is easier to define one single typeclass 
> for (+), (*) etc.
> 
> If I want to express the following idea (the following won't compiler):
> 
> data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]
> 

The reason this doesn't compile is that ValConA and ValConB are not
types.  Indeed, as their names suggest, they are value constructors.
I see what you are trying to do here, but in Haskell there is no way
to say 'the type of things which were constructed using the ValConB
constructor', you can only say 'TypeCon a' which includes values built
out of all three constructors.
 
> data TypeCon a = ValConA a | ValConB [TypeCon a] 
> 
> Which is a nightmare when I try to manipulate anything in this structure.

Right, this isn't really the same thing: this type features such fun friends as

  ValConB [ValConA 3, ValConA 6, ValConB [ValConB [ValConA 2], ValConA 9]]

and so on.

> The alternative I guess is to use 3 different type constructors,
> 
> data TypeConA a = ValConA a
> data TypeConB a = ValConB [ValConA a]
> data TypeConC a = ValConC [ValConB a]
> 
> but then I can't use one signal typeclass for (+) etc.  Am I correct?

Yes, this seems like the correct alternative to me.  What is so bad
about having three separate (smaller) type class instances?  In my
opinion that would break up the code a bit and make it easier to read
anyway, as opposed to a single monolithic instance for TypeCon.

-Brent


------------------------------

Message: 5
Date: Sun, 15 Nov 2009 22:47:53 -0500
From: Matthew Wong <matw...@rogers.com>
Subject: [Haskell-beginners] Functor question 
To: beginners@haskell.org
Message-ID: <b34a1683-8c66-4888-85a3-2c9166bc6...@rogers.com>
Content-Type: text/plain; charset=us-ascii

Hi,

When I define my data as fellow,

data Moo a = Moo a 
             deriving (Show)
             
instance Functor Moo where
    fmap f (Moo a) = Moo (f a) 

GHC gives me no problem.  Then I add something,

data (Num a) => Moo a = Moo a 
             deriving (Show)
             
instance Functor Moo where
    fmap f (Moo a) = Moo (f a) 

Now GHC gives me the follow error - see bellow.

What is the reason behind this?  What should I do to correct this?

thx,

//

matFun_v2.hs:16:12:
    Could not deduce (Num a) from the context ()
      arising from a use of `Moo' at matFun_v2.hs:16:12-14
    Possible fix:
      add (Num a) to the context of the type signature for `fmap'
    In the pattern: Moo a
    In the definition of `fmap': fmap f (Moo a) = Moo (f a)
    In the instance declaration for `Functor Moo'

matFun_v2.hs:16:21:
    Could not deduce (Num b) from the context ()
      arising from a use of `Moo' at matFun_v2.hs:16:21-29
    Possible fix:
      add (Num b) to the context of the type signature for `fmap'
    In the expression: Moo (f a)
    In the definition of `fmap': fmap f (Moo a) = Moo (f a)
    In the instance declaration for `Functor Moo'



------------------------------

Message: 6
Date: Mon, 16 Nov 2009 00:31:00 -0500
From: Matthew Wong <matw...@rogers.com>
Subject: [Haskell-beginners] Questions on data/type
To: beginners@haskell.org
Message-ID: <44134fb4-6361-4473-ae4a-b8fa53f49...@rogers.com>
Content-Type: text/plain; charset=us-ascii

Hi,

I have the following data defined.

data TypeCon a = ValConA a | ValConB [a] | ValConC [[a]]

So I can use functions with type like  (a->a->a) -> TypeCon a -> TypeCon a -> 
TypeCon a
for all 3 value types, and I think is easier to define one single typeclass for 
(+), (*) etc.

If I want to express the following idea (the following won't compiler):

data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]

Is this even a good idea?  If so how could I proceed?  The closest thing I can 
get to compiler is like this:

data TypeCon a = ValConA a | ValConB [TypeCon a] 

Which is a nightmare when I try to manipulate anything in this structure.  The 
alternative is use 3 different type constructors,

data TypeConA a = ValConA a
data TypeConB a = ValConB a
data TypeConC a = ValConC a

but then I can't use one signal typeclass for (+) etc.

thx,

//pip



------------------------------

Message: 7
Date: Mon, 16 Nov 2009 22:07:45 -0800
From: Jason Dusek <jason.du...@gmail.com>
Subject: Re: [Haskell-beginners] Functor question
To: Matthew Wong <matw...@rogers.com>
Cc: beginners@haskell.org
Message-ID:
        <42784f260911162207t1ed685b0me3b5ffcbed8ef...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

  Functor must be defined for all types -- not some restriction
  thereof (hence you see talk of indexed functors).

  Thus `fmap` needs to be typeable for any `a -> b` but the
  construcor `Moo` is only typeable at `a, b` such that we have
  both `Num a, Num b`.

--
Jason Dusek


------------------------------

Message: 8
Date: Mon, 16 Nov 2009 22:11:32 -0800
From: Jason Dusek <jason.du...@gmail.com>
Subject: Re: [Haskell-beginners] Questions on data/type
To: Matthew Wong <matw...@rogers.com>
Cc: beginners@haskell.org
Message-ID:
        <42784f260911162211i6b9e36f2xfc7779904912...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

2009/11/15 Matthew Wong <matw...@rogers.com>:
> If I want to express the following idea (the following won't compiler):
>
> data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]

  In this definition, you are confusing constructors with types.
  You can't have a list of `ValConB a` -- the type is actually
  `TypeCon a`.

> The alternative is use 3 different type constructors,
>
> data TypeConA a = ValConA a
> data TypeConB a = ValConB a
> data TypeConC a = ValConC a

  This is more promising. I'd need to see the typeclass you're
  trying to define to say more.

--
Jason Dusek


------------------------------

Message: 9
Date: Tue, 17 Nov 2009 10:56:15 +0100
From: David Virebayre <dav.vire+hask...@gmail.com>
Subject: Re: [Haskell-beginners] Question on data/type
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <4c88418c0911170156v6fdea443lc4c89d9ca6c49...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Mon, Nov 16, 2009 at 7:17 PM, Brent Yorgey <byor...@seas.upenn.edu>
wrote:

> On Mon, Nov 16, 2009 at 12:33:51AM -0500, Phillip Pirrip wrote:

>> The alternative I guess is to use 3 different type constructors,

>> data TypeConA a = ValConA a
>> data TypeConB a = ValConB [ValConA a]
>> data TypeConC a = ValConC [ValConB a]

>> but then I can't use one signal typeclass for (+) etc.  Am I correct?

> Yes, this seems like the correct alternative to me.  What is so bad

With a minor correction :

data TypeConA a = ValConA a
data TypeConB a = ValConB [TypeConA a]
data TypeConC a = ValConC [TypeConB a]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091117/987ab093/attachment-0001.html

------------------------------

Message: 10
Date: Tue, 17 Nov 2009 09:40:04 -0200
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Question on data/type
To: Phillip Pirrip <ppir...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <c2701f5c0911170340y185716c4q586e029c05929...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

(This e-mail is literate Haskell)

Not that this is the right solution to your problems, but...

> {-# LANGUAGE GADTs, EmptyDataDecls,
>              FlexibleInstances, FlexibleContexts #-}
>
> import Control.Applicative

This requires EmptyDataDecls:

> data TypeConA
> data TypeConB
> data TypeConC

We're gonna use those empty data types as phantom types in our
data type below.  This requires GADTs:

> data TypeCon t a where
>   ValConA :: a                    -> TypeCon TypeConA a
>   ValConB :: [TypeCon TypeConA a] -> TypeCon TypeConB a
>   ValConC :: [TypeCon TypeConB a] -> TypeCon TypeConC a

Using the phantom types we tell the type system what kind of
value we want.  Now, some useful instances because we can't
derive them:

> instance Show a => Show (TypeCon t a) where
>   showsPrec n x = showParen (n > 10) $
>     case x of
>       ValConA a -> showString "ValConA " . showsPrec 11 a
>       ValConB a -> showString "ValConB " . showsPrec 11 a
>       ValConC a -> showString "ValConC " . showsPrec 11 a
>
> instance Eq a => Eq (TypeCon t a) where
>   (ValConA a) == (ValConA b) = (a == b)
>   (ValConB a) == (ValConB b) = (a == b)
>   (ValConC a) == (ValConC b) = (a == b)
>   _           == _           = error "never here"

The 't' phantom type guarantees that we'll never reach that
last definition, e.g.

   *Main> (ValConA True) == (ValConB [])

   <interactive>:1:19:
       Couldn't match expected type `TypeConA'
              against inferred type `TypeConB'
         Expected type: TypeCon TypeConA Bool
         Inferred type: TypeCon TypeConB a
       In the second argument of `(==)', namely `(ValConB [])'
       In the expression: (ValConA True) == (ValConB [])

> instance Functor (TypeCon t) where
>   fmap f (ValConA a) = ValConA (f a)
>   fmap f (ValConB a) = ValConB (fmap (fmap f) a)
>   fmap f (ValConC a) = ValConC (fmap (fmap f) a)

Now, if you want applicative then you'll need FlexibleInstances
because we can't write 'pure :: a -> TypeCon t a'; this signature
means that the user of the function may choose any 't' he wants,
but we can give him only one of the 't's that appear in the
constructors above.

> instance Applicative (TypeCon TypeConA) where
>   pure x = ValConA x
>   (ValConA f) <*> (ValConA x) = ValConA (f x)
>   _           <*> _           = error "never here"
>
> instance Applicative (TypeCon TypeConB) where
>   pure x = ValConB [pure x]
>   (ValConB fs) <*> (ValConB xs) = ValConB (fmap (<*>) fs <*> xs)
>   _            <*> _            = error "never here"
>
> instance Applicative (TypeCon TypeConC) where
>   pure x = ValConC [pure x]
>   (ValConC fs) <*> (ValConC xs) = ValConC (fmap (<*>) fs <*> xs)
>   _            <*> _            = error "never here"

Now that we have applicative we can also write, using
FlexibleContexts,

> liftBinOp :: Applicative (TypeCon t) => (a->b->c)
>           -> TypeCon t a -> TypeCon t b -> TypeCon t c
> liftBinOp = liftA2

We need that 'Applicative' constraint because the type system
doesn't know that we have already defined all possible
'Applicative' instances, so we have to live with that :).

And then we can simply write

> instance (Applicative (TypeCon t), Num a) =>
>          Num (TypeCon t a) where
>   (+) = liftA2 (+)
>   (-) = liftA2 (-)
>   (*) = liftA2 (*)
>   negate = fmap negate
>   abs    = fmap abs
>   signum = fmap signum
>   fromInteger = pure . fromInteger

Finally,

   *Main> let x1 = ValConB [ValConA 10, ValConA 7]
   *Main> let x2 = ValConB [ValConA 5, ValConA 13]
   *Main> x1 * x2
   ValConB [ValConA 50,ValConA 130,ValConA 35,ValConA 91]

HTH,

--
Felipe.


------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 17, Issue 17
*****************************************

Reply via email to