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:  capital letter name in record syntax (parsing json)
      (Karl Voelker)
   2. Re:  capital letter name in record syntax (parsing json)
      (Kim-Ee Yeoh)
   3.  Signature of monadic functions (Lorenzo Tabacchini)
   4. Re:  Signature of monadic functions (Olivier Iffrig)
   5. Re:  Signature of monadic functions (Lorenzo Tabacchini)
   6. Re:  Signature of monadic functions (divyanshu ranjan)
   7. Re:  Signature of monadic functions (Daniel Trstenjak)
   8. Re:  How do I give a type for this code? (Daniel Trstenjak)


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

Message: 1
Date: Wed, 16 Oct 2013 21:24:18 -0700
From: Karl Voelker <ktvoel...@gmail.com>
To: miroslav.kar...@gmail.com,  The Haskell-Beginners Mailing List -
        Discussion of primarily beginner-level topics related to Haskell
        <beginners@haskell.org>
Subject: Re: [Haskell-beginners] capital letter name in record syntax
        (parsing json)
Message-ID:
        <caffow0z_44h+_rgoizm1+qggco8k8prducpqeduqye4ew-a...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Wed, Oct 16, 2013 at 2:18 PM, Miro Karpis <miroslav.kar...@gmail.com>wrote:

> Hi, please,...is it possible to use a capital letter in record syntax data
> definition? For example
>
> data Car =
>   Car { CarName  :: !Text
>          ,CarColor   :: !Text
>         } deriving (Show,Generic)
>
> When I try this I get: parse error on input `CarName'
>

Record field names cannot start with a capital letter. Haskell uses the
case of the first letter of a name to classify it: variables start with a
lowercase letter; constructors start with an uppercase letter.


> The thing is that I'm trying to parse a json file (with Aeson package)
> that has records starting with capital letter. After that I would like to
> parse the JSON file with following code:
>
>  d <- (eitherDecode <$> getJSON) :: IO (Either String [Car])
>
> where getJSON gets the json file from url
>
> If not, what alternative do I have?
>


If you generate your aeson instances with Data.Aeson.TH.deriveJSON, note
that the first parameter to deriveJSON is a function which lets you alter
the names. That should enable you to craft a workaround.

-Karl
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20131016/2a35dd1d/attachment-0001.html>

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

Message: 2
Date: Thu, 17 Oct 2013 12:02:20 +0700
From: Kim-Ee Yeoh <k...@atamo.com>
To: miroslav.kar...@gmail.com,  The Haskell-Beginners Mailing List -
        Discussion of primarily beginner-level topics related to Haskell
        <beginners@haskell.org>
Subject: Re: [Haskell-beginners] capital letter name in record syntax
        (parsing json)
Message-ID:
        <CAPY+ZdSRPR87LhZAr=eu1uocyrevxonume-e_+8m0dpr_nu...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Thu, Oct 17, 2013 at 4:18 AM, Miro Karpis <miroslav.kar...@gmail.com>wrote:

> Hi, please,...is it possible to use a capital letter in record syntax data
> definition? For example
>
> data Car =
>   Car { CarName  :: !Text
>          ,CarColor   :: !Text
>         } deriving (Show,Generic)
>

What Karl said.

You can prefix an underscore however: _CarName, _CarColor.

-- Kim-Ee
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20131017/e206e654/attachment-0001.html>

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

Message: 3
Date: Thu, 17 Oct 2013 09:30:17 +0200
From: "Lorenzo Tabacchini" <lorta...@gmx.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Signature of monadic functions
Message-ID: <20131017073017.256...@gmx.com>
Content-Type: text/plain; charset="utf-8"

Hi, is there an easy way to transform a function from:
 Monad m => a -> m b
to:
 Monad m => m (a -> b)
?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20131017/f9b1f1a5/attachment-0001.html>

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

Message: 4
Date: Thu, 17 Oct 2013 10:34:27 +0200
From: Olivier Iffrig <oliv...@iffrig.eu>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Signature of monadic functions
Message-ID: <20131017083427.gg29...@carbon.iffrig.eu>
Content-Type: text/plain; charset=us-ascii

Lorenzo Tabacchini wrote (2013-10-17 09:30:17 +0200):
> Hi, is there an easy way to transform a function from:
>  Monad m => a -> m b
> to:
>  Monad m => m (a -> b)

No, because there are some functions of type a -> m b which cannot be
expressed as m (a -> b), consider for instance the function

  safeRecip :: Double -> Maybe Double
  safeRecip 0 = Nothing
  safeRecip x = Just $ recip x

You can't turn that function into Maybe (Double -> Double) without
losing information about what happens to 0.

What do you want to do ?

Such "functions" of type m (a -> b) are used in the more general case of
Applicative functors to generalize fmap to functions with more than one
argument. Consider a function
  g :: a -> b -> c
Let's assume you got a Functor f, then you can use fmap to make
  fmap g :: f a -> f (b -> c).
With a Functor, you can't go much further without nesting f's, but with
an Applicative, you have
  (<*>) :: Applicative f => f (a -> b) -> f a -> f b
Control.Applicative also defines (<$>) = fmap, so you can make a
function
  fmap2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
  fmap2 g a b = g <$> a <*> b
This is exactly Control.Applicative.liftA2 (or Control.Monad.liftM2).

-- 
Olivier



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

Message: 5
Date: Thu, 17 Oct 2013 11:13:50 +0200
From: "Lorenzo Tabacchini" <lorta...@gmx.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Signature of monadic functions
Message-ID: <20131017091350.256...@gmx.com>
Content-Type: text/plain; charset="utf-8"

I think I am looking at the problem in a wrong way...

What I want to do is using higher-order functions with IO (or an IO-based 
transformer).

For example, let's say I want to apply a function to all the keys in a Map.
With pure functions, I would do:
 Map.mapKeys doSomething myMap

But let's suppose the function has a signature:
 doSomething :: a -> IO b

Is there an easy way to apply it?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20131017/e6e11506/attachment-0001.html>

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

Message: 6
Date: Thu, 17 Oct 2013 16:17:26 +0530
From: divyanshu ranjan <idivyanshu.ran...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Signature of monadic functions
Message-ID:
        <CAL9hw27K++4H6iGL0wD0W9eGJ7ZmMi+Mowz=2g7z3prbo8k...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Hi,

Map.mapKeys has constraint (Ord k2) and IO a does not provide instance of Ord.
One way to make a way around this, I can come up with is :

import Data.Map

test_a :: Map Int Int
test_a = fromList [ (i, i) | i <- [1..10] ]

print_a :: Int -> IO Int
print_a a = ( putStrLn.show $ a )  >> return a

test_b :: IO (Map Int Int)
test_b = fmap fromList $ mapM (\ (a, b) -> (do
                                              t <- print_a a
                                              return (t, b) ))  $ toList test_a

Thanks
Divyanshu Ranjan

On Thu, Oct 17, 2013 at 2:43 PM, Lorenzo Tabacchini <lorta...@gmx.com> wrote:
> I think I am looking at the problem in a wrong way...
>
> What I want to do is using higher-order functions with IO (or an IO-based
> transformer).
>
> For example, let's say I want to apply a function to all the keys in a Map.
> With pure functions, I would do:
>   Map.mapKeys doSomething myMap
>
> But let's suppose the function has a signature:
>   doSomething :: a -> IO b
>
> Is there an easy way to apply it?
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 7
Date: Thu, 17 Oct 2013 12:57:49 +0200
From: Daniel Trstenjak <daniel.trsten...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Signature of monadic functions
Message-ID: <20131017105749.GA7036@machine>
Content-Type: text/plain; charset=us-ascii


Hi Lorenzo,

all the nice abstractions like Functor, Traversable or Foldable operate
on the values of the Map. So there's 'Data.Traversable.mapM', which
almost does what you want, but only for the values of the Map.

Ok, here's a solution that does what you want:

import Data.Map
import Control.Monad

mapKeysM :: (Ord k1, Ord k2, Monad m) => (k1 -> m k2) -> Map k1 v -> m (Map k2 
v)
mapKeysM f map = return . fromList =<< mapM g (toList map)
  where
   g (key, value) = do
      key' <- f key
      return (key', value)


Certainly there has to be a solution using the lens library ...


Greetings,
Daniel


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

Message: 8
Date: Thu, 17 Oct 2013 13:13:00 +0200
From: Daniel Trstenjak <daniel.trsten...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] How do I give a type for this code?
Message-ID: <20131017111259.GA8253@machine>
Content-Type: text/plain; charset=us-ascii


Hi Todd,

the problem is, that 'model_of' tries to return different types: Model a, Model 
(a,a) and Model [a].

I think you have to use some kind of ADT also for the Model, like you already 
did for ModName.

Something like:

   data Model a = Model a
                | ProductModel (a,a)
                | PowerModel [a]
                ...


Greetings,
Daniel


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

Subject: Digest Footer

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


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

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

Reply via email to