Send Beginners mailing list submissions to
        [email protected]

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/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. Re:  How would I increment or otherwise change a value in a
      record with ?Simon-ness? (Michael Litchard)
   2. Re:  How would I increment or otherwise change a value in a
      record with ?Simon-ness? (Rein Henrichs)


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

Message: 1
Date: Wed, 5 Aug 2015 14:53:25 -0700
From: Michael Litchard <[email protected]>
To: [email protected],  The Haskell-Beginners Mailing
        List - Discussion of primarily beginner-level topics related to
        Haskell <[email protected]>
Subject: Re: [Haskell-beginners] How would I increment or otherwise
        change a value in a record with ?Simon-ness?
Message-ID:
        <CAEzeKYqwv2W0e=wzybyrzapx0trpwd2gbawacpsrjwyug3c...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I noticed the mail got archived, but I have yet to see it in my mail queue.
Is it just me? Or did something go wrong with distribution?

On Wed, Aug 5, 2015 at 2:24 PM, Sumit Sahrawat, Maths & Computing, IIT
(BHU) <[email protected]> wrote:

> More suitable for the haskell-cafe. Routing.
>
> On 6 August 2015 at 02:52, Michael Litchard <[email protected]> wrote:
>
>>
>> The below code is from this tutorial http://dev.stephendiehl.com/hask/
>>
>> it illustrates very well how to operate on values from records with
>> "Simon-ness" (illustrated below). What I am struggling with is how to
>> modify values inside records with "Simon-ness", say incrementing "age". I
>> keep thinking it has to do with the way Label is defined with the
>> constructor Get. Could I add another constructor Put?
>>
>> {-# LANGUAGE DataKinds #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE 
>> MultiParamTypeClasses #-}{-# LANGUAGE FunctionalDependencies #-}{-# LANGUAGE 
>> FlexibleInstances #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE 
>> StandaloneDeriving #-}{-# LANGUAGE ExistentialQuantification #-}{-# LANGUAGE 
>> ConstraintKinds #-}
>>
>> import GHC.TypeLits
>> newtype Field (n :: Symbol) v = Field { unField :: v } deriving Show
>> data Person1 = Person1
>>   { _age      :: Field "age" Int
>>   , _name     :: Field "name" String
>>   }
>> data Person2 = Person2
>>   { _age'  :: Field "age" Int
>>   , _name' :: Field "name" String
>>   , _lib'  :: Field "lib" String
>>   }
>> deriving instance Show Person1deriving instance Show Person2
>> data Label (l :: Symbol) = Get
>> class Has a l b | a l -> b where
>>   from :: a -> Label l -> b
>> instance Has Person1 "age" Int where
>>   from (Person1 a _) _ = unField a
>> instance Has Person1 "name" String where
>>   from (Person1 _ a) _ = unField a
>> instance Has Person2 "age" Int where
>>   from (Person2 a _ _) _ = unField a
>> instance Has Person2 "name" String where
>>   from (Person2 _ a _) _ = unField a
>>
>> age :: Has a "age" b => a -> b
>> age pnt = from pnt (Get :: Label "age")
>>
>> name :: Has a "name" b => a -> b
>> name pnt = from pnt (Get :: Label "name")
>> -- Parameterized constraint kind for "Simon-ness" of a record.type Simon a = 
>> (Has a "name" String, Has a "age" Int)
>>
>> spj :: Person1
>> spj = Person1 (Field 56) (Field "Simon Peyton Jones")
>>
>> smarlow :: Person2
>> smarlow = Person2 (Field 38) (Field "Simon Marlow") (Field "rts")
>>
>>
>> catNames :: (Simon a, Simon b) => a -> b -> String
>> catNames a b = name a ++ name b
>>
>> addAges :: (Simon a, Simon b) => a -> b -> Int
>> addAges a b = age a + age b
>>
>>
>> names :: String
>> names = name smarlow ++ "," ++ name spj-- "Simon Marlow,Simon Peyton Jones"
>>
>> ages :: Int
>> ages = age spj + age smarlow-- 94
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> [email protected]
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
>
>
> --
> Regards
>
> Sumit Sahrawat
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20150805/4aecaae2/attachment-0001.html>

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

Message: 2
Date: Thu, 06 Aug 2015 00:17:08 +0000
From: Rein Henrichs <[email protected]>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <[email protected]>,
        [email protected]
Subject: Re: [Haskell-beginners] How would I increment or otherwise
        change a value in a record with ?Simon-ness?
Message-ID:
        <CAJp6G8y5yv9zSF5dnBuUANkvFdcY41=sqo7rbezc8+ljvvi...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

This sort of thing is (relatively) nicely solved by lenses with
typeclasses, e.g.,

class HasName a where
  name :: Lens' a String

Then, with the appropriate lenses,

person ^. name
person & name .~ "Ben"
person1 ^. name
person1 & name .~ "Jerry"


On Wed, Aug 5, 2015 at 2:53 PM Michael Litchard <[email protected]> wrote:

> I noticed the mail got archived, but I have yet to see it in my mail
> queue. Is it just me? Or did something go wrong with distribution?
>
> On Wed, Aug 5, 2015 at 2:24 PM, Sumit Sahrawat, Maths & Computing, IIT
> (BHU) <[email protected]> wrote:
>
>> More suitable for the haskell-cafe. Routing.
>>
>> On 6 August 2015 at 02:52, Michael Litchard <[email protected]> wrote:
>>
>>>
>>> The below code is from this tutorial http://dev.stephendiehl.com/hask/
>>>
>>> it illustrates very well how to operate on values from records with
>>> "Simon-ness" (illustrated below). What I am struggling with is how to
>>> modify values inside records with "Simon-ness", say incrementing "age". I
>>> keep thinking it has to do with the way Label is defined with the
>>> constructor Get. Could I add another constructor Put?
>>>
>>> {-# LANGUAGE DataKinds #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE 
>>> MultiParamTypeClasses #-}{-# LANGUAGE FunctionalDependencies #-}{-# 
>>> LANGUAGE FlexibleInstances #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE 
>>> StandaloneDeriving #-}{-# LANGUAGE ExistentialQuantification #-}{-# 
>>> LANGUAGE ConstraintKinds #-}
>>>
>>> import GHC.TypeLits
>>> newtype Field (n :: Symbol) v = Field { unField :: v } deriving Show
>>> data Person1 = Person1
>>>   { _age      :: Field "age" Int
>>>   , _name     :: Field "name" String
>>>   }
>>> data Person2 = Person2
>>>   { _age'  :: Field "age" Int
>>>   , _name' :: Field "name" String
>>>   , _lib'  :: Field "lib" String
>>>   }
>>> deriving instance Show Person1deriving instance Show Person2
>>> data Label (l :: Symbol) = Get
>>> class Has a l b | a l -> b where
>>>   from :: a -> Label l -> b
>>> instance Has Person1 "age" Int where
>>>   from (Person1 a _) _ = unField a
>>> instance Has Person1 "name" String where
>>>   from (Person1 _ a) _ = unField a
>>> instance Has Person2 "age" Int where
>>>   from (Person2 a _ _) _ = unField a
>>> instance Has Person2 "name" String where
>>>   from (Person2 _ a _) _ = unField a
>>>
>>> age :: Has a "age" b => a -> b
>>> age pnt = from pnt (Get :: Label "age")
>>>
>>> name :: Has a "name" b => a -> b
>>> name pnt = from pnt (Get :: Label "name")
>>> -- Parameterized constraint kind for "Simon-ness" of a record.type Simon a 
>>> = (Has a "name" String, Has a "age" Int)
>>>
>>> spj :: Person1
>>> spj = Person1 (Field 56) (Field "Simon Peyton Jones")
>>>
>>> smarlow :: Person2
>>> smarlow = Person2 (Field 38) (Field "Simon Marlow") (Field "rts")
>>>
>>>
>>> catNames :: (Simon a, Simon b) => a -> b -> String
>>> catNames a b = name a ++ name b
>>>
>>> addAges :: (Simon a, Simon b) => a -> b -> Int
>>> addAges a b = age a + age b
>>>
>>>
>>> names :: String
>>> names = name smarlow ++ "," ++ name spj-- "Simon Marlow,Simon Peyton Jones"
>>>
>>> ages :: Int
>>> ages = age spj + age smarlow-- 94
>>>
>>>
>>> _______________________________________________
>>> Beginners mailing list
>>> [email protected]
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>>
>>>
>>
>>
>> --
>> Regards
>>
>> Sumit Sahrawat
>>
>> _______________________________________________
>> Beginners mailing list
>> [email protected]
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20150806/02654641/attachment.html>

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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
[email protected]
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 86, Issue 4
****************************************

Reply via email to