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:  Category question (Manfred Lotz)
   2.  monad transformer show help (rickmurphy)
   3. Re:  monad transformer show help (Tobias Brandt)
   4. Re:  Category question (Brent Yorgey)
   5. Re:  Category question (Manfred Lotz)
   6. Re:  State and GUI's / external interfaces /      events
      (Henry Lockyer)


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

Message: 1
Date: Tue, 29 May 2012 13:42:39 +0200
From: Manfred Lotz <manfred.l...@arcor.de>
Subject: Re: [Haskell-beginners] Category question
To: beginners@haskell.org
Message-ID: <20120529134239.4a518...@arcor.com>
Content-Type: text/plain; charset=US-ASCII

On Mon, 28 May 2012 13:43:33 -0400 (EDT)
Jay Sulzberger <j...@panix.com> wrote:


> 
> No.  The point is that, by definition, a category, call it C, is
> a struct with two sets, Obj(C) and Mor(C), and further operations:
> 
> 1. head: Mor(C) -> Obj(C)
> 
> 2. tail: Mor(C) -> Obj(C)
> 
> 3. id: Obj(C) -> Mor(C)
> 
> 4. *: Mor(C) x Mor(C) -> Mor(C)
> 
> where head and tail and id are everywhere defined single valued
> maps.  They are all maps of sets.  *, read "composition of
> morphisms" is a map of sets, with signature as displayed, but is
> not usually everywhere defined.  We have then several
> "equational" axioms, which C is required to satisfy to be a
> category.
> 
> (set theoretical note: We have, partly implicitly, ruled out
> categories which are not "small".  See standard texts for this
> locus of difficulty.)
> 
> By the axioms, any object b of C must have defined its associated
> identity morphism id[b].  For many categories, b will always be
> an actual set, and id[b] will be the unique map of sets defined
> by
> 
>    (id[b])(x) = x , for all x in b
> 
> where (id[b])(x) is read "the result of applying id[b] to the element
> x of b".
> 
> But, as explained, many categories have objects which are not
> sets.  Indeed, often, no object is a set.
> 
> The definition of category never mentions whether or not the
> objects are sets.  And, as we have seen, there are many
> categories whose objects are not sets.  (Perhaps categorically
> better: many categories are not directly presented as having
> objects which are sets.)
> 
> to repeat: The concept "category" is larger in extension than the
> concept "category whose objects are sets and whose morphisms are
> maps of sets".
> 
> ad representations of categories:
> 
>    http://en.wikipedia.org/wiki/Yoneda_Lemma
>    [page was last modified on 1 April 2012 at 05:17]
> 
> >
> >
> > I guess that this made me think of idA as idA(x) = x for each x of
> > A. Later when I saw other (more general) definitions I did not read
> > carefully to realize the difference.
> >
> >
> > Thanks a lot for making this clear to me.
> >
> >
> > -- 
> > Manfred
> 
> I will let stand my restatement of what you already know ;)
> 
> oo--JS.
> 

Thanks a lot for the detailed example and explanations. I will study
your post thoroughly.



-- 
Manfred





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

Message: 2
Date: Tue, 29 May 2012 08:35:29 -0400
From: rickmurphy <r...@rickmurphy.org>
Subject: [Haskell-beginners] monad transformer show help
To: beginners <beginners@haskell.org>
Message-ID: <1338294929.2302.20.camel@metho-laptop>
Content-Type: text/plain; charset="UTF-8"

Hello All:

Over the past few days I got my first exposure to monad transformers.

I worked through the sample below. 

The witness w displays IC 0 as expected, but even after providing the
instance of show for type O I a, witness w' causes ghci to display

    No instance for (Num (I' a0))
      arising from a use of w'
    Possible fix: add an instance declaration for (Num (I' a0))

Would someone be able to explain why after providing the instance of
show on O I a, w' does not print the expected result (OC (IC 0)) ?

BTW - You will notice the sample intentionally avoids the use of
deriving (Show) on newtype I.

--
Rick


{-# LANGUAGE NoMonomorphismRestriction, DatatypeContexts,
FlexibleContexts, FlexibleInstances #-}

module Main where

import Control.Monad
import Control.Monad.Trans.Class

<snip>

-- |A parameterized new type I representing an "inner type" with one
constructor IC               
newtype I a = IC a -- deriving (Show)

-- |Unwraps the value in the inner type 
unI (IC x) = x

-- |A monad instance on the inner type
instance Monad I where
 return = IC
 m >>= f = f (unI m)

instance Show a => Show (I a) where
 show (IC x) = "IC " ++ show x

-- |Witness on inner type
w :: Num a => I a
w = (IC 0) >>= return . id

-- |A parameterized new type O m a representing an "outer type" with a
named constructor 
newtype O m a = OC {runO :: m (I a)} -- deriving (Show)

-- |?
instance Show a => Show (O I a) where
 show (OC x) = "OC (IC " ++ show (unI x) ++ "))" -- show (OC (IC 0))

-- |Unwraps the value in the outer type 
unO (OC (IC a)) = a

-- |A monad transformer instance on type O m a 
instance Monad m => Monad (O m) where
 return = OC . return . IC 
 m >>= f = OC $ do {v <- runO m; runO (f (unI v))}

-- | Witness on monad transformer
w' :: Num (I a) => O I a
w' = (OC (IC 0)) >>= return . id

-- | Executes addition on the zero in IC
w'' :: Num a => I a
w'' = liftM (+1) (IC' 0)

-- |Instance of monad transformer lift on O m a
instance MonadTrans O where
 lift m = OC (m >>= return . IC)

-- |Executes addition on the zero in IC and lifts to O m a
w''' :: (Num a, MonadTrans t) => t I a
w''' = lift ((IC 0) >>= return . (+1))




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

Message: 3
Date: Tue, 29 May 2012 15:23:56 +0200
From: Tobias Brandt <tob.bra...@googlemail.com>
Subject: Re: [Haskell-beginners] monad transformer show help
To: rickmurphy <r...@rickmurphy.org>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <caoowqip78tvhoo6mm3lbs1ft8rculgzyacwcqirtgvqqgdm...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On 29 May 2012 14:35, rickmurphy <r...@rickmurphy.org> wrote:
> w' :: Num (I a) => O I a
> w' = (OC (IC 0)) >>= return . id

w' requires a Num instance for 'I a', but there is none.

You need to define:

instance Num a => Num (I a) where
   ...

by lifting all operations into I.



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

Message: 4
Date: Tue, 29 May 2012 09:31:01 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Category question
To: beginners@haskell.org
Message-ID: <20120529133101.ga9...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, May 28, 2012 at 06:50:34PM +0200, Manfred Lotz wrote:
> On Mon, 28 May 2012 10:57:11 -0400
> Brent Yorgey <byor...@seas.upenn.edu> wrote:
> 
> > On Mon, May 28, 2012 at 04:14:40PM +0200, Manfred Lotz wrote:
> > > 
> > > For me id: A -> A could be defined by: A morphism id: A -> A is
> > > called identity morphism iff for all x of A we have  id(x) = x.
> > 
> > This is not actually a valid definition; the notation id(x) = x does
> > not make sense.  It seems you are assuming that morphisms represent
> > some sort of function, but that is only true in certain special
> > categories.
> > 
> 
> Ok, it is a valid definition only in a certain context. In the
> far wider context of category theory this indeed makes no sense.

Right.

 
> In 'Conceptual Mathematics' by F. William Lawvere, Stephen H. Schanuel
> they define an identity map with fa = a for each a in A.
> Then on page 17 they define category and say 
> 
> ...
> Identity Maps: (one per object) 1A: A -> A
> ...
> Rules for a category
> 1. The identity laws:
> where they say g . 1A = g and 1B . f = f
> 2. associatlve laws
> ...
> 
> It seems that this definition of a category is not as general as it
> could be. Here 1. is something which follows easily from the definition
> of an identity map.

I am guessing (though I have not looked at 'Conceptual Mathematics' in
detail) that they use 'an identity map with fa = a for each a in A'
simply as an *example* to help build intuition; then on page 17 they
generalize this example to the fully abstract definition of a
category. It does seem unfortunate that they continue to use the name
'identity map', because morphisms/arrows are more general than 'maps'
(to me, 'map' is synonymous with 'function').

-Brent



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

Message: 5
Date: Tue, 29 May 2012 17:11:01 +0200
From: Manfred Lotz <manfred.l...@arcor.de>
Subject: Re: [Haskell-beginners] Category question
To: beginners@haskell.org
Message-ID: <20120529171101.261fb...@arcor.com>
Content-Type: text/plain; charset=US-ASCII

On Tue, 29 May 2012 09:31:01 -0400
Brent Yorgey <byor...@seas.upenn.edu> wrote:

> On Mon, May 28, 2012 at 06:50:34PM +0200, Manfred Lotz wrote:
> > On Mon, 28 May 2012 10:57:11 -0400
> > Brent Yorgey <byor...@seas.upenn.edu> wrote:
> > 
> > > On Mon, May 28, 2012 at 04:14:40PM +0200, Manfred Lotz wrote:
> > > > 
> > > > For me id: A -> A could be defined by: A morphism id: A -> A is
> > > > called identity morphism iff for all x of A we have  id(x) = x.
> > > 
> > > This is not actually a valid definition; the notation id(x) = x
> > > does not make sense.  It seems you are assuming that morphisms
> > > represent some sort of function, but that is only true in certain
> > > special categories.
> > > 
> > 
> > Ok, it is a valid definition only in a certain context. In the
> > far wider context of category theory this indeed makes no sense.
> 
> Right.
> 
>  
> > In 'Conceptual Mathematics' by F. William Lawvere, Stephen H.
> > Schanuel they define an identity map with fa = a for each a in A.
> > Then on page 17 they define category and say 
> > 
> > ...
> > Identity Maps: (one per object) 1A: A -> A
> > ...
> > Rules for a category
> > 1. The identity laws:
> > where they say g . 1A = g and 1B . f = f
> > 2. associatlve laws
> > ...
> > 
> > It seems that this definition of a category is not as general as it
> > could be. Here 1. is something which follows easily from the
> > definition of an identity map.
> 
> I am guessing (though I have not looked at 'Conceptual Mathematics' in
> detail) that they use 'an identity map with fa = a for each a in A'
> simply as an *example* to help build intuition; then on page 17 they
> generalize this example to the fully abstract definition of a
> category. It does seem unfortunate that they continue to use the name
> 'identity map', because morphisms/arrows are more general than 'maps'
> (to me, 'map' is synonymous with 'function').
> 

Yes, even in the general definition they use identity map. IMHO, they
should have made it clearer that there is a broader context. 

But anyway, the discussion here was fruitful and thanks to you and the
others it is now clear to me. 



-- 
Manfred





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

Message: 6
Date: Tue, 29 May 2012 16:41:10 +0100
From: Henry Lockyer <henry.lock...@ntlworld.com>
Subject: Re: [Haskell-beginners] State and GUI's / external interfaces
        /       events
To: Beginners@haskell.org
Message-ID: <98a4d603-51c5-4d1c-a2c1-df5e4db8b...@ntlworld.com>
Content-Type: text/plain; charset="us-ascii"

If I haven't already scared everyone off..
Sorry for rather wordy original question/s below - struggling late at night to 
get at it reasonably clearly (or think at all, for that matter) ! 

Anyway, just to clarify regarding 'question 2' slightly: This was not meant to 
be completely naieve (though maybe it still was ;-) 
in that I appreciate the basic functional/purity/referential transparency issue 
but was getting confused looking at it in this context.
I guess in effect I'm asking if there is some cunning way with FFI that 
sequencing of incoming external function calls can be 
maintained to enable state based decisions to then be made in the Haskell 
domain. 
It becomes more of a message/signal passing solution then rather than a basic 
subroutine type function call, and the Haskell 
program could then treat them similarly to my toy example program for example - 
get next signal from the buffer, or use
lazy IO type approach to treat them as a larger construct etc. 

(I am not including the kind of solution here where the whole state data is 
threaded in and out in every function, which
does not count as 'maintaining the state in the Haskell domain').

Question 1 is a side issue really, and re question 3, and FFI in question 2, I 
know I know there is online material etc. 
to read but I keep getting a little way up each staircase in easy steps then 
find there is a hole that will take some
time to bridge...  But nonetheless, any reading recommendations are welcome in 
case I missed a good one!

On 29 May 2012, at 01:15, Henry Lockyer wrote:

> Hi all,
> I'm trying to straighten out my basic understanding around state-based IO 
> handling in Haskell.
> 
> I've been reading around in several places but it hasn't clicked yet, and the 
> input buffer is now cluttered with 
> new things to assimilate ;-)
> 
> The basic question is about what ways there are to implement state-based 
> decisions, where an external event of some kind 
> results in some Haskell function/s being called depending on the particular 
> event and the current state, then
> perhaps some new external action initiated, and new state set.  Basic state 
> machine type of logic.
> 
> As a starting point I include down at the bottom of this mail a little 
> example program which implements something 
> like this for terminal IO.  The state/logic could be made arbitrarily more 
> complex.
> It's a simple 'event loop' that blocks on getChar until a Char is input, with 
> a separate pure event/state query function.
> 
> One could also implement the per-Char state-based handling using the State 
> monad by mapping over 
> the Char inputs as a string, for example something like:
> 
> main = do hSetBuffering stdin NoBuffering
>          interact \str -> evalState ( mapM charfunc str ) initstate
>            where charfunc :: Char -> State Char Char
>                      . . .
> I'm not sure how I would implement the exit case if I used this approach for 
> the 'aha!' game below though.
> 
> Anyway, a few interrelated questions running out from this general starting 
> point:
> 
> 1. I've not really played with monad transformers yet, but I  guess one could 
> use monad transformers to 
>   make a combined IO/State monad as an alternative to the basic solution down 
> below.  
>   Assuming there is no lurking problem with doing that, does it help? 
>   (I can't see much advantage, in this case where explicitly manipulating the 
> state at each step is the main activity.)
> 
> 2. The 'event loop' in IO in the example below drives the state 
> lookup/branching logic, but how can you separate
>    the sequential state logic from the polling process?   This is really the 
> nub of my question.
>    I'm not familiar with the FFI or the GUI libraries, so with apologies in 
> advance for misunderstanding it all...
>     say for example we want to implement a Haskell program that responds to 
> events arriving as external 
>     function calls via the FFI where the state-based logic is in Haskell but 
> the events are not polled for, they
>     just arrive (for example could be driven by some main loop in external 
> functionality, eg. GUI). 
>     We want the Haskell implementation to respond in a sequential state-based 
> manner so that if
>     the external events/calls 'a', 'a', 'h' arrive this could produce 
> different responses (to the second and third events)
>     compared to the event sequence 'a', 'h', 'a'. 
>     How/can you do this in Haskell?
>     The events could come from some completely independent and/or 
> uncontrollable sources but we require the
>     Haskell program to respond according to arrival sequence.   
>     My intuition says that this is not possible if the events arrive simply 
> as independent function calls on an
>     external interface, but that they must be collected somehow into a single 
> sequential 
>     entity such as a file, list, 'stream' or somesuch and then they can be 
> mapped over or some kind of read loop can 
>     pull them off in sequence as in the example below.   But I am probably 
> wrong :)     ?
> 
> 3. What state/event handling model do the GUI solutions like whhaskell or 
> gtk2hs use? I read that they use callbacks,
>    which makes sense, but does it mean that the callbacks must be manipulated 
> (or some associated widget attributes) so as
>    to encode the state back into the GUI at every step?  In other words the 
> first 'a' in the above "aah" vs "aha" example
>    would have to, as a minimum, initiate a change in the callback/attributes 
> of the 'a' generator so that the second
>    'a' will actually be a different 'a' ( 'a2' perhaps) or carry some 
> additional parameter info so that the correct function in the
>    receiving Haskell is invoked?  This could be horrible if there are, say, 
> 50 different widgets that could generate the next event
>    and they would all have to be updated to reflect each state change.  I 
> feel it must be better than this somehow..  
>    So how does it work?   
> 
> Any help appreciated.
> Thanks/ Henry
> 
> --
> -- "aha!" 
> --
> -- An exciting game that requires the string "aha!" to
> -- be entered in order to reach the exit.
> --
> 
> import System.IO
> 
> type MyState = Char
> 
> initstate, exitstate :: MyState
> initstate = 'a'
> exitstate = 'z'
> 
> main :: IO ()
> main = do hSetBuffering stdin NoBuffering
>          stateIO initstate
> 
> stateIO :: MyState -> IO ()
> stateIO s = do c_in <- getChar
>               let (c_out, s') = stateMC c_in s
>               putStrLn $ ' ':c_out:[]
>               if s' /= exitstate then stateIO s' 
>                                  else putStrLn "Bye..."
> 
> stateMC :: Char -> MyState -> (Char, MyState)
> stateMC 'a' 'a' = ('Y', 'b')
> stateMC 'h' 'b' = ('Y', 'c')
> stateMC 'a' 'c' = ('Y', 'd')
> stateMC '!' 'd' = ('*', 'z')
> stateMC  _   _  = ('N', 'a')
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120529/b5c1ade8/attachment.htm>

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

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


End of Beginners Digest, Vol 47, Issue 28
*****************************************

Reply via email to