Send Beginners mailing list submissions to
[email protected]
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
[email protected]
You can reach the person managing the list at
[email protected]
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."
Today's Topics:
1. am I wording this right? (Michael P Mossey)
2. Re: am I wording this right? (Peter Verswyvelen)
3. Re: am I wording this right? (Michael P Mossey)
4. Re: am I wording this right? (Peter Verswyvelen)
5. fmap fmap (Michael P Mossey)
6. Re: fmap fmap (Felipe Lessa)
7. Re: fmap fmap (Isaac Dupree)
8. Re: fmap fmap (Jason Dusek)
9. Re: am I wording this right? (Jason Dusek)
10. Re: fmap fmap (Tony Morris)
11. RE: Getting the Takusen example code to compile -failed
import problem (Daniel Everett)
----------------------------------------------------------------------
Message: 1
Date: Tue, 04 Aug 2009 16:07:22 -0700
From: Michael P Mossey <[email protected]>
Subject: [Haskell-beginners] am I wording this right?
To: beginners <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
Is this the right way of saying what I'm trying to say?
"Functor is a typeclass of type constructors which take one argument."
Thanks,
Mike
------------------------------
Message: 2
Date: Wed, 5 Aug 2009 02:15:44 +0200
From: Peter Verswyvelen <[email protected]>
Subject: Re: [Haskell-beginners] am I wording this right?
To: Michael P Mossey <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
That sound okay to me.
Usually when we have type constructor "T a" and an "instance Functor T
where..." we just say that "T is a functor"
Note that the signature of a type constructor is called the "kind" of
the type constructor.
For example, the following code
data NotSoKind = X
instance Functor NotSoKind where
would give the error:
Kind mis-match
Expected kind `* -> *', but `NotSoKind' has kind `*'
In the instance declaration for `Functor NotSoKind'
and
instance Functor (,) where
gives the error
(,)' is not applied to enough type arguments
Expected kind `* -> *', but `(,)' has kind `* -> * -> *'
In the instance declaration for `Functor (,)'
Note however that the following is correct:
instance Functor ((,) a) where
fmap f (x,y) = (x, f y)
and even:
instance Functor ((->) a) where
fmap f g = f . g
You can ask GHCi to show the kind of a type constructor:
:kind (,)
(,) :: * -> * -> *
:kind ((,) 1)
((,) 1) :: * -> *
:kind Char
*
On Wed, Aug 5, 2009 at 1:07 AM, Michael P Mossey <[email protected]>
wrote:
>
> Is this the right way of saying what I'm trying to say?
>
> "Functor is a typeclass of type constructors which take one argument."
>
> Thanks,
> Mike
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
------------------------------
Message: 3
Date: Tue, 04 Aug 2009 17:25:04 -0700
From: Michael P Mossey <[email protected]>
Subject: Re: [Haskell-beginners] am I wording this right?
To: beginners <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
Peter Verswyvelen wrote:
>
> Note however that the following is correct:
>
> instance Functor ((,) a) where
> fmap f (x,y) = (x, f y)
>
> and even:
>
> instance Functor ((->) a) where
> fmap f g = f . g
>
Thanks. What's curious to me about these instances is that they have a type
variable a which is never referenced in the definition.
Is there ever a case in which you would refer to the type variable 'a'
somewhere
in the definition of an instance? I know that the types of the "member
functions" of the instance are given in the class definition, so there is no
place to put a type definition in the instance, I don't think.
Thanks,
Mike
------------------------------
Message: 4
Date: Wed, 5 Aug 2009 02:39:07 +0200
From: Peter Verswyvelen <[email protected]>
Subject: Re: [Haskell-beginners] am I wording this right?
To: Michael P Mossey <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
On Wed, Aug 5, 2009 at 2:25 AM, Michael P Mossey<[email protected]> wrote:
> Peter Verswyvelen wrote:
>> Note however that the following is correct:
>>
>> instance Functor ((,) a) where
>> fmap f (x,y) = (x, f y)
>>
>
> Thanks. What's curious to me about these instances is that they have a type
> variable a which is never referenced in the definition.
>
> Is there ever a case in which you would refer to the type variable 'a'
> somewhere in the definition of an instance? I know that the types of the
> "member functions" of the instance are given in the class definition, so
> there is no place to put a type definition in the instance, I don't think.
Good question, I don't know.
You can use it to add constraints, e.g.
instance Show a => Functor ((,) a) where
fmap f (x,y) = (x, f y)
but the "a" type does not seem to be available in the definitions,
it's scope seems to be limited, e.g.
instance Functor ((,) a) where
fmap f (x,y) = (x::a, f y)
doesn't compile. But I'm just guessing here, don't know the details :-(
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
------------------------------
Message: 5
Date: Tue, 04 Aug 2009 18:02:29 -0700
From: Michael P Mossey <[email protected]>
Subject: [Haskell-beginners] fmap fmap
To: beginners <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
How does one write
fmap (fmap (*2)) xs
without parenthesis? (Using . and $ instead.)
I don't really understand . and $ well enough I guess. I tried a bunch of stuff
but nothing worked.
-Mike
------------------------------
Message: 6
Date: Tue, 4 Aug 2009 22:16:08 -0300
From: Felipe Lessa <[email protected]>
Subject: Re: [Haskell-beginners] fmap fmap
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
On Tue, Aug 04, 2009 at 06:02:29PM -0700, Michael P Mossey wrote:
> How does one write
>
> fmap (fmap (*2)) xs
>
> without parenthesis? (Using . and $ instead.)
fmap (fmap (*2)) xs
flip fmap xs (fmap (*2))
flip fmap xs $ fmap (*2)
flip fmap xs $ fmap (\x -> (*) x 2)
flip fmap xs $ fmap (\x -> flip (*) 2 x)
flip fmap xs $ fmap (flip (*) 2)
flip fmap xs $ fmap $ flip (*) 2
--
Felipe.
------------------------------
Message: 7
Date: Tue, 04 Aug 2009 21:17:56 -0400
From: Isaac Dupree <[email protected]>
Subject: Re: [Haskell-beginners] fmap fmap
To: Michael P Mossey <[email protected]>
Cc: beginners <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
Michael P Mossey wrote:
> How does one write
>
> fmap (fmap (*2)) xs
>
> without parenthesis? (Using . and $ instead.)
I don't think it's possible?
"(fmap . fmap) (*2) xs" might be something you like, though.
(also, the parentheses from (*2) are section syntax and can't just be
removed in the same way)
-Isaac
------------------------------
Message: 8
Date: Tue, 4 Aug 2009 18:49:38 -0700
From: Jason Dusek <[email protected]>
Subject: Re: [Haskell-beginners] fmap fmap
To: Michael P Mossey <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=UTF-8
2009/08/04 Michael P Mossey <[email protected]>:
> fmap (fmap (*2)) xs
Not exactly what you asked for:
fmap (*2) `fmap` xs
Operator sections -- the `(*2)` -- require parens. Using
backticks helps you clean up parenthesis.
--
Jason Dusek
------------------------------
Message: 9
Date: Tue, 4 Aug 2009 18:54:14 -0700
From: Jason Dusek <[email protected]>
Subject: Re: [Haskell-beginners] am I wording this right?
To: Michael P Mossey <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=UTF-8
2009/08/04 Michael P Mossey <[email protected]>:
> Is there ever a case in which you would refer to the type
> variable 'a' somewhere in the definition of an instance?
When using overloaded functions to write the instance -- for
example, `fmap` or `mappend` -- you might place type
signatures on them to disambiguate.
--
Jason Dusek
------------------------------
Message: 10
Date: Wed, 05 Aug 2009 13:29:51 +1000
From: Tony Morris <[email protected]>
Subject: Re: [Haskell-beginners] fmap fmap
To: Michael P Mossey <[email protected]>
Cc: beginners <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
Michael P Mossey wrote:
> How does one write
>
> fmap (fmap (*2)) xs
>
> without parenthesis? (Using . and $ instead.)
>
> I don't really understand . and $ well enough I guess. I tried a bunch
> of stuff but nothing worked.
>
> -Mike
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
fmap . fmap $ (*2)
or perhaps:
(fmap . fmap) (*2)
--
Tony Morris
http://tmorris.net/
------------------------------
Message: 11
Date: Thu, 6 Aug 2009 18:21:19 +0000 (GMT)
From: Daniel Everett <[email protected]>
Subject: RE: [Haskell-beginners] Getting the Takusen example code to
compile -failed import problem
To: AlistairBayley <[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=iso-8859-1
> >
> > I have Takusen 0.8.5 installed and I'm trying to build
> the
> > code found at
> > http://darcs.haskell.org/takusen/doc/html/Database-Enumerator.
> html using ghc 6.10.3. This always fails with the
> error:
> >
> > Could not find module `Database.Oracle.Enumerator'
> >
> > The analogous errors are encountered if I substitute
> Oracle
> > with Sqlite, Postgresql or ODBC. Any ideas how
> to resolve this?
>
>
OK, this now compiles thanks to (a) hacking Setup.hs to refer to odbc_config
rather than odbcconf and (b) unregistering the user packages with ghc-pkg
--user unregister Takusen.
However, if I then create a table in MySQL with:
create table dummy (id int primary key);
and then use a reduced form of the example code:
import Database.Enumerator
import Database.ODBC.Enumerator
import Control.Monad.Trans(liftIO)
query1Iteratee :: (Monad m) => Int -> String -> Double -> IterAct m [(Int,
String, Double)]
query1Iteratee a b c accum = result' ((a, b, c):accum)
main :: IO ()
main = do
withSession (connect "DSN=test") ( do
-- simple query, returning reversed list
of rows.
r <- doQuery (sql "select id from dummy")
query1Iteratee []
liftIO(putStrLn(show r))
)
then I get the error:
fromUTF8Ptr: zero byte found in string as position 8
Is there any thing wrong with the above code?
Also, what does liftIO actually do? Its documentation at
http://cvs.haskell.org/Hugs/pages/libraries/mtl/Control-Monad-Trans.html does
not actually say! The link at the top of that page is dead as well.
Regards,
Daniel
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 14, Issue 4
****************************************