Send Beginners mailing list submissions to
        beginners@haskell.org

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
        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 parse hetero-list (Baa)
   2.  how to undertand  the function    join (*) (=?gb18030?B?UmF5?=)
   3. Re:  how to undertand  the function    join (*) (Frerich Raabe)
   4.  Overlapping instances problem (Baa)


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

Message: 1
Date: Thu, 30 Nov 2017 15:03:18 +0200
From: Baa <aqua...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] How to parse hetero-list
Message-ID: <20171130150318.59f366cb@Pavel>
Content-Type: text/plain; charset=US-ASCII

Hmm, I done it with:

  infixl 9 |||
  data a ||| b = A a|B b deriving Show


  instance (Read a, Read b) => Read (a ||| b) where
    readPrec = parens $ do
      a <- (A <$> readPrec) <|> (B <$> readPrec)
      return a

so parse looks like:

  read "1" :: Int ||| Char ||| String

but I'm not sure is other more classical way to do it...


> Hello, All!
> 
> I have types A, B, C... They have instances of class Read, Show,
> SomethingElse, ... I want to keep them as one collection. For example,
> I can use such datatype for it:
> 
>   data Tags = forall a. Read a => Tags [a]
> 
> Now I want to parse "some-string" into A or B or C or ... but without
> to create type's sum of A|B|C|...! All those types have `Read`
> instance but Haskell will not find what instance to use, right? How
> to parse string with alternatives where each alternative returns
> `ReadP A` or `ReadP B`, etc? My intuition is that I should make `x
> <|> y <|> z <|> ...` where x,y,z - parses string into A, B, C, ... so
> they are expressions like `readPrec :: ReadPrec A`, etc. But how to
> pass types into such expression? I must to make expression folding
> (with `<|>`) `readPrec::someType`, where `someType` is item of types
> list `{A, B, C, ...}`
> 
> May be it's possible to be done with HList-like types, like: HSet,
> HVect or similar, but I don't know:
> 
>   - how to iterate/fold over types
>   - I'm not sure that HSet/HVect keeps types (like `A ::: B :::
> C ::: ...`)
> 
> My idea is to have some function which can parse string into one of
> A|B|C|... with call like:
> 
>   myParse "some-string" :: (Something A ::: B ::: C ::: D)
> 
> (suppose `:::` is type-level "cons"). So, `myParse` is polymorphic and
> it can fold/iterate over type-list items (to call appropriate
> `readPrec`).
> 
> Is it even possible?
> 
> In languages with reflection I can pass list of types (type - is usual
> value) and call type's methods, but how to solve similar in Haskell?
> 
> ===
> Best regards, Paul



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

Message: 2
Date: Thu, 30 Nov 2017 21:18:46 +0800
From: "=?gb18030?B?UmF5?=" <122234...@qq.com>
To: "=?gb18030?B?YmVnaW5uZXJz?=" <beginners@haskell.org>
Subject: [Haskell-beginners] how to undertand  the function    join
        (*)
Message-ID: <tencent_3fb07ea121713627ba122897ce1294be2...@qq.com>
Content-Type: text/plain; charset="gb18030"

Hello Marcus,

what does join (*) do?

 

(*) :: Num a => a -> a -> a

join (*) :: Num a => a -> a




when we feed a number to join (*),for instance;

 λ> : join (*) 3 

 9

it seems thata join (*) become a square function.

what does join do to  (*) to make that happen?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20171130/3fc65bc3/attachment-0001.html>

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

Message: 3
Date: Thu, 30 Nov 2017 14:47:37 +0100
From: Frerich Raabe <ra...@froglogic.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] how to undertand  the function
        join (*)
Message-ID: <edd3c458457e76441ba5db6cf1d3c...@froglogic.com>
Content-Type: text/plain; charset=UTF-8; format=flowed

On 2017-11-30 14:18, Ray wrote:
> what does JOIN (*) do?
> 
> (*) :: Num a => a -> a -> a
> 
> join (*) :: Num a => a -> a
> 
> when we feed a number to join (*),for instance;
> 
>  λ> : join (*) 3
> 
>  9
> 
> it seems thata JOIN (*) become a square function.
> 
> what does JOIN do to  (*) to make that happen?

You can figure it out by using equational reasoning and evaluating the 
expression manually:

   join (*) 3

Function application is left-associative, so this is equivalent to

   (join (*)) 3

The 'join' function is defined as 
(http://hackage.haskell.org/package/base-4.10.0.0/docs/src/GHC.Base.html#join)

   join x = x >>= id

So we can replace 'join (*)' in our above expression with

   ((*) >>= id) 3

(>>=) for functions is defined as

   f >>= k = \ r -> k (f r) r

So with that at hand, we get

   (\r -> id ((*) r) r) 3

'id x' is just 'x', so we get

   (\r -> (*) r r) 3

With infix syntax, this can be written as

   (\r -> r * r) 3

If you now apply that function, you get

   3 * 3

Which gives your result '9'.

-- 
Frerich Raabe - ra...@froglogic.com
www.froglogic.com - Multi-Platform GUI Testing


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

Message: 4
Date: Fri, 1 Dec 2017 13:57:56 +0200
From: Baa <aqua...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] Overlapping instances problem
Message-ID: <20171201135756.5ac0c43d@Pavel>
Content-Type: text/plain; charset=US-ASCII

Hello, List!

I got error:

 Duplicate instance declarations:
   instance [overlap ok] EnumTag a => Read a
     -- Defined at /XXX/intero/intero2932Xpa-TEMP.hs:110:27
   instance [overlap ok] StrTag a => Read a
     -- Defined at /XXX/intero/intero2932Xpa-TEMP.hs:121:27 (intero)

For this code:

  class (Show a, Enum a) => EnumTag a where
    anyEnum :: a

  instance {-# OVERLAPS #-} EnumTag a => Read a where
    readPrec = RP.lift P.skipSpaces >> expectEnum
  instance {-# OVERLAPS #-} EnumTag a => Eq a where
    a == b | a == anyEnum || b == anyEnum = True
          | otherwise = fromEnum a == fromEnum b

  class StrTag a where
    anyStr :: a
    tagPrefix :: a -> String -- ^ should be constant
    toStr :: String -> a

  instance {-# OVERLAPS #-} StrTag a => Read a where
    readPrec = parens $ do
      RP.lift P.skipSpaces
      (RP.lift $ expectShown anyStr) <++ RP.lift g
      where g = do
              Just s@(_:_) <- L.stripPrefix tagPrefix <$> expectTag
              return $ toStr s

Why does it happen? `Read a` in 1st instance is valid only when a is
`EnumTag`, in 2nd one - is valid only when a is `StrTag`.

How can I fix this error and to create "default" instances for `EnumTag`
and to `StrTag`, so client code will "inherit" those functionality
(`Read`) simple, only with instantiation of `EnumTag` or `StrTag` ?

Sure, if I comment `instance ... StrTag a` then all work fine, but I need 2 
specialized `Read`s (and `Eq`s too :)

===
Best regards, Paul


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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 114, Issue 1
*****************************************

Reply via email to