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.  Re: How to import the Data.Char library in Hugs?
      (Benjamin L.Russell)
   2.  Re: How to import the Data.Char library in Hugs?
      (Benjamin L.Russell)
   3. Re:  Re: How to import the Data.Char library in   Hugs?
      (Daniel Fischer)
   4.  Re: How to import the Data.Char library in Hugs?
      (Benjamin L.Russell)
   5.  Re: How to import the Data.Char library in Hugs?
      (Benjamin L.Russell)
   6.  Re: Maybe, Either (Heinrich Apfelmus)
   7. Re:  Re: How to import the Data.Char library in   Hugs?
      (Daniel Fischer)
   8.  type class question (Ben)


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

Message: 1
Date: Fri, 18 Sep 2009 11:27:31 +0900
From: Benjamin L.Russell <dekudekup...@yahoo.com>
Subject: [Haskell-beginners] Re: How to import the Data.Char library
        in Hugs?
To: beginners@haskell.org
Message-ID: <0sr5b5524g1078cv68dt1vm1vsaagsr...@4ax.com>
Content-Type: text/plain; charset=us-ascii

On Thu, 17 Sep 2009 15:04:07 +0200, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:

>Am Donnerstag 17 September 2009 14:41:47 schrieb Benjamin L.Russell:
>> My apologies if this is an extremely elementary question, but I am
>> having difficulties in importing the Data.Char library in Hugs.
>
>Hugs> :a Data.Char
>Data.Char>

Thank you; that was exactly the information for which I was looking.

Incidentally, what option name does 'a' represent?  That one doesn't
appear when I type ":?."  Shouldn't it appear in that list?

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 



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

Message: 2
Date: Fri, 18 Sep 2009 11:39:50 +0900
From: Benjamin L.Russell <dekudekup...@yahoo.com>
Subject: [Haskell-beginners] Re: How to import the Data.Char library
        in Hugs?
To: beginners@haskell.org
Message-ID: <8ks5b5t6snt7de6sf1irclis3oftjub...@4ax.com>
Content-Type: text/plain; charset=us-ascii

On Thu, 17 Sep 2009 15:02:21 +0200, Adrian Neumann
<aneum...@inf.fu-berlin.de> wrote:

>You do
>
>> :l Data.Char

That command didn't work; see the following results:

--8<---------------cut here---------------start------------->8---
Hugs>:| Data.Char
Command not recognised.  Type :? for help
Hugs>
--8<---------------cut here---------------end--------------->8---

-- Benjamin L. Russell

>
>As far as I know you can't have multiple loaded modules unless you put
>them in a file and load that.
>
>Regards,
>
>Adrian
>
>Benjamin L.Russell schrieb:
>> My apologies if this is an extremely elementary question, but I am
>> having difficulties in importing the Data.Char library in Hugs.
>> 
>> In GHCi, the command "import Data.Char" works correctly, as follows:
>> 
>> --8<---------------cut here---------------start------------->8---
>> GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
>> Loading package ghc-prim ... linking ... done.
>> Loading package integer ... linking ... done.
>> Loading package base ... linking ... done.
>>    ___         ___ _
>>   / _ \ /\  /\/ __(_)
>>  / /_\// /_/ / /  | |   GHC Interactive, for Haskell 98.
>> / /_\\/ __  / /___| |   http://www.haskell.org/ghc/
>> \____/\/ /_/\____/|_|   Type :? for help.
>> 
>> Prelude> import Data.Char
>> Prelude Data.Char>
>> --8<---------------cut here---------------end--------------->8---
>> 
>> However, in Hugs, the same command fails with an error, as follows:
>> 
>> --8<---------------cut here---------------start------------->8---
>> __   __ __  __  ____   ___ _________________________________________
>> ||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98 standard
>> ||___|| ||__|| ||__||  __||     Copyright (c) 1994-2005
>> ||---||         ___||           World Wide Web: http://haskell.org/hugs
>> ||   ||                         Bugs: http://hackage.haskell.org/trac/hugs
>> ||   || Version: 20051031       _________________________________________
>> 
>> Haskell 98 mode: Restart with command line option -98 to enable
>> extensions
>> 
>> Type :? for help
>> Hugs> import Data.Char
>> ERROR - Syntax error in expression (unexpected keyword "import")
>> Hugs>
>> --8<---------------cut here---------------end--------------->8---
>> 
>> Does anybody know how to import the Data.Char library in Hugs?
>> 
>> -- Benjamin L. Russell
>
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 



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

Message: 3
Date: Fri, 18 Sep 2009 04:52:17 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: How to import the Data.Char
        library in      Hugs?
To: beginners@haskell.org
Message-ID: <200909180452.18071.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Freitag 18 September 2009 04:27:31 schrieb Benjamin L.Russell:
> On Thu, 17 Sep 2009 15:04:07 +0200, Daniel Fischer
>
> <daniel.is.fisc...@web.de> wrote:
> >Am Donnerstag 17 September 2009 14:41:47 schrieb Benjamin L.Russell:
> >> My apologies if this is an extremely elementary question, but I am
> >> having difficulties in importing the Data.Char library in Hugs.
> >
> >Hugs> :a Data.Char
> >Data.Char>
>
> Thank you; that was exactly the information for which I was looking.
>
> Incidentally, what option name does 'a' represent?  That one doesn't
> appear when I type ":?."  Shouldn't it appear in that list?

It should, and it does for me (hugs september 2006):

Hugs> :?
LIST OF COMMANDS:  Any command may be abbreviated to :c where
c is the first character in the full name.

:load <filenames>   load modules from specified files
:load               clear all files except prelude
:also <filenames>   read additional modules         <--- There
:reload             repeat last load command

Unfortunately, Hugs' behaviour is much less convenient than ghci's:

Hugs> :also Data.Char SimplTest
SimplTest> ord 'a'
ERROR - Undefined variable "ord"
SimplTest> Data.Char.ord 'a'
ERROR - Undefined qualified variable "Data.Char.ord"

You can't directly use it, neither qualified nor unqualified, you have to 
switch contexts 
with :m(odule):

SimplTest> :m Data.Char
Data.Char> ord 'a'
97
Data.Char> :m SimplTest
SimplTest> filter (test 4) $ digl 3
[[0,0,0],[0,1,4],[0,2,8],[1,4,0],[1,5,4],[1,6,8],[2,8,0],[2,9,4]]

>
> -- Benjamin L. Russell



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

Message: 4
Date: Fri, 18 Sep 2009 13:25:43 +0900
From: Benjamin L.Russell <dekudekup...@yahoo.com>
Subject: [Haskell-beginners] Re: How to import the Data.Char library
        in Hugs?
To: beginners@haskell.org
Message-ID: <nc26b5p48ov523hkvuhv0vuorju5078...@4ax.com>
Content-Type: text/plain; charset=us-ascii

On Fri, 18 Sep 2009 04:52:17 +0200, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:

>Am Freitag 18 September 2009 04:27:31 schrieb Benjamin L.Russell:
>> On Thu, 17 Sep 2009 15:04:07 +0200, Daniel Fischer
>>
>> <daniel.is.fisc...@web.de> wrote:
>> >Am Donnerstag 17 September 2009 14:41:47 schrieb Benjamin L.Russell:
>> >> My apologies if this is an extremely elementary question, but I am
>> >> having difficulties in importing the Data.Char library in Hugs.
>> >
>> >Hugs> :a Data.Char
>> >Data.Char>
>>
>> Thank you; that was exactly the information for which I was looking.
>>
>> Incidentally, what option name does 'a' represent?  That one doesn't
>> appear when I type ":?."  Shouldn't it appear in that list?
>
>It should, and it does for me (hugs september 2006):
>
>Hugs> :?
>LIST OF COMMANDS:  Any command may be abbreviated to :c where
>c is the first character in the full name.
>
>:load <filenames>   load modules from specified files
>:load               clear all files except prelude
>:also <filenames>   read additional modules         <--- There
>:reload             repeat last load command

Oops; you're right:  The structure of the two commands above it was
the following:

>:load <filenames>   load modules from specified files
>:load               clear all files except prelude

Apparently, for some reason, when I tried to scan through the list, I
subconsciously grouped the two commands below similarly:

>:also <filenames>   read additional modules
>:reload             repeat last load command

Therefore, I somehow only read the second line of what I thought was a
structurally similar second group, and therefore noticed the
":reload," but not the ":also," expecting the command above it to be
":reload <filenames>."

I probably should have either read more slowly (I was rushing out to
lunch at the time), or somehow avoided unconsciously assuming patterns
that didn't exist.

Too much mental pattern-matching ;-).

>
>Unfortunately, Hugs' behaviour is much less convenient than ghci's:
>
>Hugs> :also Data.Char SimplTest
>SimplTest> ord 'a'
>ERROR - Undefined variable "ord"
>SimplTest> Data.Char.ord 'a'
>ERROR - Undefined qualified variable "Data.Char.ord"
>
>You can't directly use it, neither qualified nor unqualified, you have to 
>switch contexts 
>with :m(odule):
>
>SimplTest> :m Data.Char
>Data.Char> ord 'a'
>97
>Data.Char> :m SimplTest
>SimplTest> filter (test 4) $ digl 3
>[[0,0,0],[0,1,4],[0,2,8],[1,4,0],[1,5,4],[1,6,8],[2,8,0],[2,9,4]]

Interesting; what happens if I then need to use a higher-order
function composed of other functions, some of which are from different
modules, interactively?

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 



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

Message: 5
Date: Fri, 18 Sep 2009 15:05:46 +0900
From: Benjamin L.Russell <dekudekup...@yahoo.com>
Subject: [Haskell-beginners] Re: How to import the Data.Char library
        in Hugs?
To: beginners@haskell.org
Message-ID: <db86b5dgn0ks74tk5ere773avm6b8ga...@4ax.com>
Content-Type: text/plain; charset=us-ascii

My apologies; another respondent in this forum responded in a private
e-mail message that I had misrecognized your ":l" (a colon followed by
a lowercase 'L') for a vertical bar; I was using a variable-width
font; perhaps I should have double-checked using a fixed-width font.

I stand (er, sit, rather) corrected, as follows:

--8<---------------cut here---------------start------------->8---
Hugs>:l Data.Char
Data.Char>:?
--8<---------------cut here---------------end--------------->8---

Incidentally, if WinHugs cannot have multiple loaded modules unless
they are put in a file and loaded therein, then what is the difference
between the ":l" (a colon followed by a lowercase 'L') and ":a" (a
colon followed by a lowercase 'A') commands?

-- Benjamin L. Russell

On Fri, 18 Sep 2009 11:39:50 +0900, Benjamin L.Russell
<dekudekup...@yahoo.com> wrote:

>On Thu, 17 Sep 2009 15:02:21 +0200, Adrian Neumann
><aneum...@inf.fu-berlin.de> wrote:
>
>>You do
>>
>>> :l Data.Char
>
>That command didn't work; see the following results:
>
>--8<---------------cut here---------------start------------->8---
>Hugs>:| Data.Char
>Command not recognised.  Type :? for help
>Hugs>
>--8<---------------cut here---------------end--------------->8---
>
>-- Benjamin L. Russell
>
>>
>>As far as I know you can't have multiple loaded modules unless you put
>>them in a file and load that.
>>
>>Regards,
>>
>>Adrian
>>
>>Benjamin L.Russell schrieb:
>>> My apologies if this is an extremely elementary question, but I am
>>> having difficulties in importing the Data.Char library in Hugs.
>>> 
>>> In GHCi, the command "import Data.Char" works correctly, as follows:
>>> 
>>> --8<---------------cut here---------------start------------->8---
>>> GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
>>> Loading package ghc-prim ... linking ... done.
>>> Loading package integer ... linking ... done.
>>> Loading package base ... linking ... done.
>>>    ___         ___ _
>>>   / _ \ /\  /\/ __(_)
>>>  / /_\// /_/ / /  | |   GHC Interactive, for Haskell 98.
>>> / /_\\/ __  / /___| |   http://www.haskell.org/ghc/
>>> \____/\/ /_/\____/|_|   Type :? for help.
>>> 
>>> Prelude> import Data.Char
>>> Prelude Data.Char>
>>> --8<---------------cut here---------------end--------------->8---
>>> 
>>> However, in Hugs, the same command fails with an error, as follows:
>>> 
>>> --8<---------------cut here---------------start------------->8---
>>> __   __ __  __  ____   ___ _________________________________________
>>> ||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98 standard
>>> ||___|| ||__|| ||__||  __||     Copyright (c) 1994-2005
>>> ||---||         ___||           World Wide Web: http://haskell.org/hugs
>>> ||   ||                         Bugs: http://hackage.haskell.org/trac/hugs
>>> ||   || Version: 20051031       _________________________________________
>>> 
>>> Haskell 98 mode: Restart with command line option -98 to enable
>>> extensions
>>> 
>>> Type :? for help
>>> Hugs> import Data.Char
>>> ERROR - Syntax error in expression (unexpected keyword "import")
>>> Hugs>
>>> --8<---------------cut here---------------end--------------->8---
>>> 
>>> Does anybody know how to import the Data.Char library in Hugs?
>>> 
>>> -- Benjamin L. Russell
>>
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 



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

Message: 6
Date: Fri, 18 Sep 2009 11:05:02 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: Maybe, Either
To: beginners@haskell.org
Message-ID: <h8vifu$b9...@ger.gmane.org>
Content-Type: text/plain; charset=UTF-8

Yusaku Hashimoto wrote:
> If I understood your post correctly, you said
> 
> - generalizing lookup to MonadPlus or Alternative or such classes are
> not necessary

In particular, it doesn't become more general, it becomes less general
(in a sense).

> - use Maybe as usual, we should use adapters as we need
> 
> Conor, You have said this many times elsewhere, but unfortunately, I
> heard it for the first time =) so please correct me if I'm wrong.
> 
> I thought generalizing lookup is good example for usage of the
> MonadPlus as I read in RWH[1], but you said it's not necessary.
> 
> Now, I understood there are two positions for such classes. One is
> using generalizing for it, another is not.
> 
> So, I want to know that when such classes should be used from later position.
> 
> Heinrich suggested that is for overloading.

To elaborate on generality versus overloading: the function

     lookupM :: MonadPlus m => k -> Map k a -> m a

is not more general than

     lookup :: k -> Map k a -> Maybe a

because you can implement the former with the latter

     lookupM k = mop . lookup k

     mop = maybe mzero return

In other words,  lookupM  doesn't introduce new functionality.


Rather, it gives you the syntactic convenience of not having to mention
 mop  by overloading the result type. In other words, you can write

     lookup  = lookupM

or

     lookupE :: k -> Map k a -> Either e a
     lookupE = lookupM


> But do any other usages are exist?

I'm not quite sure I understand what you mean here?


Regards,
apfelmus

--
http://apfelmus.nfshost.com



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

Message: 7
Date: Fri, 18 Sep 2009 12:25:56 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: How to import the Data.Char
        library in      Hugs?
To: beginners@haskell.org
Message-ID: <200909181225.56378.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Freitag 18 September 2009 08:05:46 schrieb Benjamin L.Russell:
> Incidentally, if WinHugs cannot have multiple loaded modules unless
> they are put in a file and loaded therein, then what is the difference
> between the ":l" (a colon followed by a lowercase 'L') and ":a" (a
> colon followed by a lowercase 'A') commands?

The difference is that :load loads one module (and its imports) and forgets 
previously 
loaded modules, while :also doesn't forget the previously loaded modules.
So if you first load a large project (A), evaluate some expressions in that 
context, then 
switch to a different project (B), and then switch back, if you use
A> :a B
B> some expression
some result
B> :m A
A>
the last A> prompt should be there pretty immediately, while in
A> :l B
B> some expression
some result
B> :l A
A>
the last A> prompt will take a while, since the entire project has to be lexed, 
parsed and 
compiled (to whatever intermediate representation Hugs uses) again.


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

Message: 8
Date: Fri, 18 Sep 2009 07:38:19 -0700
From: Ben <midfi...@gmail.com>
Subject: [Haskell-beginners] type class question
To: beginners@haskell.org
Message-ID:
        <9157df230909180738m38797aacta2bc94b3631f3...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

dear haskellers --

this email is an (il)literate haskell file.

suppose i have class of computations a -> State s b.  for
concreteness, let's say i'm writing a library of on-line statistical
summary functions, like

> {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances 
> #-}
>
> module Foo where
>
> import Control.Monad
> import Control.Monad.State
> import Control.Monad.State.Class
>
> data RunningAverageState = S Double Int
>
> runningAverage :: Double -> State RunningAverageState Double
> runningAverage v = do
>                    S sum count <- get
>                    let nsum = sum + v
>                        ncount = count + 1
>                    put $ S nsum ncount
>                    return $ nsum / (fromIntegral ncount)
>
> test = take 10 $ evalState (mapM runningAverage [1..]) $ S 0 0

test -> [1.0,1.5,2.0,2.5,3.0,3.5,4.0,4.5,5.0,5.5]

here "on-line" means that we may be taking data from an intermittant
external source, e.g. a data generator IO [Double], say, and want to
be able to feed the summarizer datum one-by-one, and produce
intermediate summaries.  also we may want to be able to serialize our
computation state (with Data.Binary, say) so that we can resume data
collection and summarization later.

naturally i want to create some common higher order operations on
these primitives, like applying them to a stream of data, or combining
them in some way.  it seems that one would want some kind of type
class to define a common interface to them.

> class (MonadState s m) => Summarizer s m | m -> s where
>     initialState :: s
>     runOne :: Double -> m Double
>

where initialize puts some intial state into the system, and runOne
collects and summarizes the next piece of data.  an instance for
runningAverage would look like

> instance Summarizer RunningAverageState (State RunningAverageState) where
>    initialState = S 0 0
>    runOne = runningAverage

but how would i use this, e.g.

> --summarizeMany vs = last $ evalState (mapM runOne vs) initialState

does not compile.

1) what am i doing wrong?  what are the right type class and instance
declarations?

2) is there a better way of expressing this kind of "on-line"
calculation, perhaps in pure (non-monadic) functions?

best, ben


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

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


End of Beginners Digest, Vol 15, Issue 13
*****************************************

Reply via email to