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 write Read instance (Baa)
   2. Re:  How to write Read instance (Baa)
   3. Re:  How to write Read instance (Baa)
   4. Re:  How to write Read instance (Baa)


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

Message: 1
Date: Thu, 2 Nov 2017 17:13:43 +0200
From: Baa <aqua...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] How to write Read instance
Message-ID: <20171102171343.76a1c322@Pavel>
Content-Type: text/plain; charset=US-ASCII

Does it work with wrapping in records, in "Just" ?
Would you show this example, please?

I try this:

  import qualified Data.Text           as T
  import           GHC.Read
  import qualified Data.Char           as C

  newtype GitHash = GitHash { ghValue :: T.Text } deriving (Eq, Ord, Generic)

  instance Show GitHash where
    show = T.unpack . ghValue

  instance Read GitHash where
    readsPrec p = readParen (p > 10) reader where
      reader :: ReadS GitHash
      reader s =
         case span C.isHexDigit s of
           ([], _)      -> []
           (hex, nohex) -> [(GitHash $ T.pack hex, nohex)]
    readListPrec = readListPrecDefault
    readList     = readListDefault

and this parses:

  > read "1234ab"::GitHash

but not this:

  > read "Just 1234"::Maybe GitHash
  *** Exception: Prelude.read: no parse



> My own toy example works.  I don't know how yours differs.
> 
> On Thu, Nov 2, 2017 at 10:51 AM, Baa <aqua...@gmail.com> wrote:
> 
> > Hello, David!
> >
> > `Show` instance is simple:
> >
> >   instance Show Hex where
> >     show = T.unpack . ghValue
> >
> > so
> >  
> >   > show (Hex "1234ab")  
> >   1234ab  
> >   > read "1234ab"::Hex  
> >   1234ab  
> >   > read "Just 1234ab"::Maybe Hex -- fails like wrapped in the
> >   > record!!  
> >
> > Yes, I'm ignoring precedence usually too. And I return rest of the
> > string. Playing with `UTCTime`'s readsPrec shows me that behaviour
> > looks the same: UTCTime's reader returns the same rest. So, may be
> > trick is in the:
> >
> > 1. Precedence ?!
> > 2. readListPrec = readListPrecDefault
> >    readList     = readListDefault   ?
> >
> >    But I get error: readListPrec is not visible method of class
> > Read... 3. readPrec ? I implemented readsPrec which is old-style,
> > but am I right that old-style and new-style are absolutely the same
> > from reading point of view and old-style can replace new-style and
> > vice versa?
> >
> > PS. I don't import any special modules.
> >
> >  
> > > The most common way is to just auto derive Read.  I'm not sure
> > > that that ever really fails.  Are you sure the problem isn't with
> > > the Show instance of the type?  People commonly write invalid
> > > Show instances to make them look pretty and they shouldn't.  read
> > > and show are supposed to be inverses of each other because when
> > > they aren't, problems like this occur.
> > >
> > > The simple way to do a Read instance is to implement the reads
> > > function for it.  The confusion comes from its type.  readsPrec ::
> > > Int -> ReadS a. ReadS is defined as String -> [(a, String)],
> > > where a is the parsed result and String is the rest of the string
> > > that is being parsed, , which may look confusing, and the Int is
> > > precedence, which can usually be ignored.  It could have been Int
> > > -> String -> Maybe (a, String), but Read predates Maybe.  So
> > > instead it returns a list and if it fails to parse, it returns []
> > > instead of Nothing.  So.
> > >
> > > data MyFoo = MyFoo
> > >
> > > instance Read MyFoo where
> > >   -- readsPrec :: Int -> String -> [(MyFoo, String)]
> > >   readsPrec _ = readFoo
> > >
> > > readFoo :: String -> [(MyFoo, String)]
> > > readFoo str = case splitAt 5 str of
> > >   ("MyFoo", rest) -> [(MyFoo, rest)]
> > >   otherwise -> []
> > >
> > > If you need something more complex, there are functions to do it
> > > in base that perform lexing and parsing.  I have never used them
> > > but you can go ahead and read some of the instances such as
> > > Ordering at
> > > https://hackage.haskell.org/package/base-4.10.0.0/docs/  
> > src/GHC.Read.html#line-398  
> > > to try and learn how it might work for you.
> > >
> > > But honestly I think you should look at fixing your Show instance
> > > first, if possible.
> > >
> > >
> > > On Thu, Nov 2, 2017 at 9:41 AM, Baa <aqua...@gmail.com> wrote:
> > >  
> > > > Hello all!
> > > >
> > > > I found some errors in the reading of previously shown big and
> > > > complex record. Reason is: some of fields are reading wrongly.
> > > > So, is there any useful documents how to write `Read` instance
> > > > correctly (because I can't find good tutorial in the Web and
> > > > often hit errors with `Read` instance)? May be
> > > > tutorial/examples/any good info...
> > > >
> > > >
> > > > ===
> > > > Best regards, Paul
> > > > _______________________________________________
> > > > Beginners mailing list
> > > > Beginners@haskell.org
> > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> > > >  
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> >  



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

Message: 2
Date: Thu, 2 Nov 2017 17:17:09 +0200
From: Baa <aqua...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] How to write Read instance
Message-ID: <20171102171709.597c46b5@Pavel>
Content-Type: text/plain; charset=US-ASCII

Hmm, difference is that your example with "Foo" uses fixed (ident)
lexem. But when you need to return rest of the string which is not part
of your type - this leads to problem for me...

> The most common way is to just auto derive Read.  I'm not sure that
> that ever really fails.  Are you sure the problem isn't with the Show
> instance of the type?  People commonly write invalid Show instances
> to make them look pretty and they shouldn't.  read and show are
> supposed to be inverses of each other because when they aren't,
> problems like this occur.
> 
> The simple way to do a Read instance is to implement the reads
> function for it.  The confusion comes from its type.  readsPrec ::
> Int -> ReadS a. ReadS is defined as String -> [(a, String)], where a
> is the parsed result and String is the rest of the string that is
> being parsed, , which may look confusing, and the Int is precedence,
> which can usually be ignored.  It could have been Int -> String ->
> Maybe (a, String), but Read predates Maybe.  So instead it returns a
> list and if it fails to parse, it returns [] instead of Nothing.  So.
> 
> data MyFoo = MyFoo
> 
> instance Read MyFoo where
>   -- readsPrec :: Int -> String -> [(MyFoo, String)]
>   readsPrec _ = readFoo
> 
> readFoo :: String -> [(MyFoo, String)]
> readFoo str = case splitAt 5 str of
>   ("MyFoo", rest) -> [(MyFoo, rest)]
>   otherwise -> []
> 
> If you need something more complex, there are functions to do it in
> base that perform lexing and parsing.  I have never used them but you
> can go ahead and read some of the instances such as Ordering at
> https://hackage.haskell.org/package/base-4.10.0.0/docs/src/GHC.Read.html#line-398
> to try and learn how it might work for you.
> 
> But honestly I think you should look at fixing your Show instance
> first, if possible.
> 
> 
> On Thu, Nov 2, 2017 at 9:41 AM, Baa <aqua...@gmail.com> wrote:
> 
> > Hello all!
> >
> > I found some errors in the reading of previously shown big and
> > complex record. Reason is: some of fields are reading wrongly. So,
> > is there any useful documents how to write `Read` instance correctly
> > (because I can't find good tutorial in the Web and often hit errors
> > with `Read` instance)? May be tutorial/examples/any good info...
> >
> >
> > ===
> > Best regards, Paul
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> >  



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

Message: 3
Date: Thu, 2 Nov 2017 17:27:53 +0200
From: Baa <aqua...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] How to write Read instance
Message-ID: <20171102172753.56a426f4@Pavel>
Content-Type: text/plain; charset=US-ASCII

David, it's very strange! My snippet works with "Just" and wrapping in
a record too, but only if I surround hex-number with ( and ):

  "D {d = (123abc)}"
       or
  "Just (123abc)"

If I remove call of `readParen` then it can parse strings like:

  "D {d = 123abc}"

but can not like

  "Just 123abc"

> My own toy example works.  I don't know how yours differs.
> 
> On Thu, Nov 2, 2017 at 10:51 AM, Baa <aqua...@gmail.com> wrote:
> 
> > Hello, David!
> >
> > `Show` instance is simple:
> >
> >   instance Show Hex where
> >     show = T.unpack . ghValue
> >
> > so
> >  
> >   > show (Hex "1234ab")  
> >   1234ab  
> >   > read "1234ab"::Hex  
> >   1234ab  
> >   > read "Just 1234ab"::Maybe Hex -- fails like wrapped in the
> >   > record!!  
> >
> > Yes, I'm ignoring precedence usually too. And I return rest of the
> > string. Playing with `UTCTime`'s readsPrec shows me that behaviour
> > looks the same: UTCTime's reader returns the same rest. So, may be
> > trick is in the:
> >
> > 1. Precedence ?!
> > 2. readListPrec = readListPrecDefault
> >    readList     = readListDefault   ?
> >
> >    But I get error: readListPrec is not visible method of class
> > Read... 3. readPrec ? I implemented readsPrec which is old-style,
> > but am I right that old-style and new-style are absolutely the same
> > from reading point of view and old-style can replace new-style and
> > vice versa?
> >
> > PS. I don't import any special modules.
> >
> >  
> > > The most common way is to just auto derive Read.  I'm not sure
> > > that that ever really fails.  Are you sure the problem isn't with
> > > the Show instance of the type?  People commonly write invalid
> > > Show instances to make them look pretty and they shouldn't.  read
> > > and show are supposed to be inverses of each other because when
> > > they aren't, problems like this occur.
> > >
> > > The simple way to do a Read instance is to implement the reads
> > > function for it.  The confusion comes from its type.  readsPrec ::
> > > Int -> ReadS a. ReadS is defined as String -> [(a, String)],
> > > where a is the parsed result and String is the rest of the string
> > > that is being parsed, , which may look confusing, and the Int is
> > > precedence, which can usually be ignored.  It could have been Int
> > > -> String -> Maybe (a, String), but Read predates Maybe.  So
> > > instead it returns a list and if it fails to parse, it returns []
> > > instead of Nothing.  So.
> > >
> > > data MyFoo = MyFoo
> > >
> > > instance Read MyFoo where
> > >   -- readsPrec :: Int -> String -> [(MyFoo, String)]
> > >   readsPrec _ = readFoo
> > >
> > > readFoo :: String -> [(MyFoo, String)]
> > > readFoo str = case splitAt 5 str of
> > >   ("MyFoo", rest) -> [(MyFoo, rest)]
> > >   otherwise -> []
> > >
> > > If you need something more complex, there are functions to do it
> > > in base that perform lexing and parsing.  I have never used them
> > > but you can go ahead and read some of the instances such as
> > > Ordering at
> > > https://hackage.haskell.org/package/base-4.10.0.0/docs/  
> > src/GHC.Read.html#line-398  
> > > to try and learn how it might work for you.
> > >
> > > But honestly I think you should look at fixing your Show instance
> > > first, if possible.
> > >
> > >
> > > On Thu, Nov 2, 2017 at 9:41 AM, Baa <aqua...@gmail.com> wrote:
> > >  
> > > > Hello all!
> > > >
> > > > I found some errors in the reading of previously shown big and
> > > > complex record. Reason is: some of fields are reading wrongly.
> > > > So, is there any useful documents how to write `Read` instance
> > > > correctly (because I can't find good tutorial in the Web and
> > > > often hit errors with `Read` instance)? May be
> > > > tutorial/examples/any good info...
> > > >
> > > >
> > > > ===
> > > > Best regards, Paul
> > > > _______________________________________________
> > > > Beginners mailing list
> > > > Beginners@haskell.org
> > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> > > >  
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> >  



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

Message: 4
Date: Thu, 2 Nov 2017 18:45:37 +0200
From: Baa <aqua...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] How to write Read instance
Message-ID: <20171102184537.7d5c1006@Pavel>
Content-Type: text/plain; charset=US-ASCII

David, your experience and intuition were absolutely right: solution is
in the right Show and Read pair. So, this seems to work in all cases:

  import qualified Text.ParserCombinators.ReadP as P
  import           Text.ParserCombinators.ReadPrec (lift)
  import qualified Data.Char           as C

  -- |Type of Git hashes
  newtype GitHash = GitHash { ghValue :: T.Text } deriving (Eq, Ord, Generic)

  instance Show GitHash where
    showsPrec p a = showParen (p > 10) (showString $ T.unpack $ ghValue a)

  hexDigits :: P.ReadP String
  hexDigits = P.munch1 C.isHexDigit

  instance Read GitHash where
    readPrec = parens $ do
      lift P.skipSpaces
      s::String <- lift hexDigits
      return $ GitHash $ T.pack s


Thanks a lot again!!


> My own toy example works.  I don't know how yours differs.
> 
> On Thu, Nov 2, 2017 at 10:51 AM, Baa <aqua...@gmail.com> wrote:
> 
> > Hello, David!
> >
> > `Show` instance is simple:
> >
> >   instance Show Hex where
> >     show = T.unpack . ghValue
> >
> > so
> >  
> >   > show (Hex "1234ab")  
> >   1234ab  
> >   > read "1234ab"::Hex  
> >   1234ab  
> >   > read "Just 1234ab"::Maybe Hex -- fails like wrapped in the
> >   > record!!  
> >
> > Yes, I'm ignoring precedence usually too. And I return rest of the
> > string. Playing with `UTCTime`'s readsPrec shows me that behaviour
> > looks the same: UTCTime's reader returns the same rest. So, may be
> > trick is in the:
> >
> > 1. Precedence ?!
> > 2. readListPrec = readListPrecDefault
> >    readList     = readListDefault   ?
> >
> >    But I get error: readListPrec is not visible method of class
> > Read... 3. readPrec ? I implemented readsPrec which is old-style,
> > but am I right that old-style and new-style are absolutely the same
> > from reading point of view and old-style can replace new-style and
> > vice versa?
> >
> > PS. I don't import any special modules.
> >
> >  
> > > The most common way is to just auto derive Read.  I'm not sure
> > > that that ever really fails.  Are you sure the problem isn't with
> > > the Show instance of the type?  People commonly write invalid
> > > Show instances to make them look pretty and they shouldn't.  read
> > > and show are supposed to be inverses of each other because when
> > > they aren't, problems like this occur.
> > >
> > > The simple way to do a Read instance is to implement the reads
> > > function for it.  The confusion comes from its type.  readsPrec ::
> > > Int -> ReadS a. ReadS is defined as String -> [(a, String)],
> > > where a is the parsed result and String is the rest of the string
> > > that is being parsed, , which may look confusing, and the Int is
> > > precedence, which can usually be ignored.  It could have been Int
> > > -> String -> Maybe (a, String), but Read predates Maybe.  So
> > > instead it returns a list and if it fails to parse, it returns []
> > > instead of Nothing.  So.
> > >
> > > data MyFoo = MyFoo
> > >
> > > instance Read MyFoo where
> > >   -- readsPrec :: Int -> String -> [(MyFoo, String)]
> > >   readsPrec _ = readFoo
> > >
> > > readFoo :: String -> [(MyFoo, String)]
> > > readFoo str = case splitAt 5 str of
> > >   ("MyFoo", rest) -> [(MyFoo, rest)]
> > >   otherwise -> []
> > >
> > > If you need something more complex, there are functions to do it
> > > in base that perform lexing and parsing.  I have never used them
> > > but you can go ahead and read some of the instances such as
> > > Ordering at
> > > https://hackage.haskell.org/package/base-4.10.0.0/docs/  
> > src/GHC.Read.html#line-398  
> > > to try and learn how it might work for you.
> > >
> > > But honestly I think you should look at fixing your Show instance
> > > first, if possible.
> > >
> > >
> > > On Thu, Nov 2, 2017 at 9:41 AM, Baa <aqua...@gmail.com> wrote:
> > >  
> > > > Hello all!
> > > >
> > > > I found some errors in the reading of previously shown big and
> > > > complex record. Reason is: some of fields are reading wrongly.
> > > > So, is there any useful documents how to write `Read` instance
> > > > correctly (because I can't find good tutorial in the Web and
> > > > often hit errors with `Read` instance)? May be
> > > > tutorial/examples/any good info...
> > > >
> > > >
> > > > ===
> > > > Best regards, Paul
> > > > _______________________________________________
> > > > Beginners mailing list
> > > > Beginners@haskell.org
> > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> > > >  
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> >  



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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 113, Issue 2
*****************************************

Reply via email to