instance declaration and convert string to Maybe type - haskell

An guessing and answering game.
Each Card comprises a Suit, one of A,B,C,D,E,F,G, and a Rank, one of 1|2|3.
I need to have a function to guarantee input(String) whether is valid type. And also write an instance declaration so that the type is in the Show class.
I am not sure about the function toCard, how to express "String" in the function and meet it with the condition.
data Suit = A|B|C|D|E|F|G
deriving (Show , Eq)
data Rank = R1|R2|R3
deriving (Show, Eq)
data Card = Card Suit Rank
deriving (Show, Eq)
instance Show Card where show (Card a b)
= show a ++ show (tail show b)
toCard :: String -> Maybe Card
toCard all#(x:xs)
| (x=A|B|C|D|E|F)&&(xs==1|2|3) = Just Card
| otherwise = Nothing
edit toCard function, input should be any String, so i use a list expression, but it seems to be not correct, cause i try it in ghci, (x=A|B|C|D|E|F)&&(y==1|2|3) is not valid

1) Firstly,
instance Show Card where show (Card a b)
= show a ++ show (tail show b)
You have automatically derived a Show instance for Card, so this will conflict (you can only have 1 instance), and further it won't compile. The show should go on a new line, and tail should be applied to the result of show b.
instance Show Card where
show (Card a b) = show a ++ " " + tail (show b)
2) Secondly,
toCard :: String -> Maybe Card
toCard all#(x:xs)
| (x=A|B|C|D|E|F)&&(xs==1|2|3) = Just Card
| otherwise = Nothing
The syntax (x=A|B|C|D|E|F)&&(xs==1|2|3) is pretty wild, and certainly not valid Haskell. The closest approximation would be something like, x `elem` ['A','B','C','D','E','F'] && xs `elem` ["1","2","3"], but as you can see this rapidly becomes boilerplate-y. Also, Just Card makes no sense - you still need to use the x and xs to say what the card actually is! eg. Just $ Card x xs (though that still won't work because they're still character/string not Suit/Rank).
One solution would be to automatically derive a Read instance on Rank, Suit, and Card. However, the automatic derivation for read on Card would require you to input eg. "Card A R1", so let's try using the instance on Rank and Suit to let us write a parser for Cards that doesn't require prefixed "Card".
First attempt:
toCard :: String -> Maybe Card
toCard (x:xs) = Just $ Card (read [x] :: Suit) (read xs :: Rank)
Hmm, this doesn't really allow us to deal with bad inputs - problem being that read just throws errors instead of giving us a Maybe. Notice however that we use [x] rather than x because read applies to [Char] and x :: Char. Next attempt:
import Text.Read (readMaybe)
toCard :: String -> Maybe Card
toCard [] = Nothing
toCard (x:xs) = let mSuit = readMaybe [x] :: Suit
mRank = readMaybe xs :: Rank
in case (mSuit, mRank) of
(Just s, Just r) -> Just $ Card s r
_ -> Nothing
This copes better with bad inputs, but has started to get quite long. Here's two possible ways to shorten it again:
-- using the Maybe monad
toCard (x:xs) = do mSuit <- readMaybe [x]
mRank <- readMaybe xs
return $ Card mSuit mRank
-- using Applicative
toCard (x:xs) = Card <$> readMaybe [x] <*> readMaybe xs

A parser library, though it comes with a steeper learning curve, makes this simpler. For this example, we'll use Text.Parsec, from the parsec library. Import it, and define a type alias for using in defining your parsers.
import Text.Parsec
type Parser = Parsec String () -- boilerplate
Parsec String () indicates a type of parser that consumes a stream of characters, and can produce a value of type () after parsing is complete. (In this case, we only care about the parsing, not any computation done along side the parsing.)
For your core types, we'll define a Show instant by hand for Rank so that you don't need to strip the R off later. We'll also derive a Read instance for Suit to make it easier to convert a string like "A" to a Suit value like A.
data Suit = A|B|C|D|E|F|G deriving (Show, Read, Eq)
data Rank = R1|R2|R3 deriving (Eq)
-- Define Show yourself so you don't constantly have to remove the `R`
instance Show Rank where
show R1 = "1"
show R2 = "2"
show R3 = "3"
data Card = Card Suit Rank deriving Eq
instance Show Card where
show (Card s r) = show s ++ show r
With that out of the way, we can define some parsers for each type.
-- Because oneOf will fail if you don't get one
-- of the valid suit characters, read [s] is guaranteed
-- to succeed. Using read eliminates the need for a
-- large case statement like in rank, below.
suit :: Parser Suit
suit = do
s <- oneOf "ABCDEF"
return $ read [s]
rank :: Parser Rank
rank = do
n <- oneOf "123"
return $ case n of
'1' -> R1
'2' -> R2
'3' -> R3
-- A Card parser just combines the Suit and Rank parsers
card :: Parser Card
card = Card <$> suit <*> rank
-- parse returns an Either ParseError Card value;
-- you can ignore the exact error if the parser fails
-- to return Nothing instead.
toCard :: String -> Maybe Card
toCard s = case parse card "" s of
Left _ -> Nothing
Right c -> Just c
oneOf is a predefined parser that consumes exactly one of the items in the given list.
parse takes three arguments:
A parser
A "source name" (only used for error message; you can use any string you like)
The string to parse

Related

How to do a Read instance for a simple custom format of data

I'm trying to use a short and easy to read format to show and read my data, and I would like that it could be used from the Haskell interpreter, in order to write hand or copy-paste inputs while I try new functions.
My data is a list of Int numbers, each one with an boolean property, that I associate with + and -, being the first one the default, so it doesn't need explicit representation (as with usual sign). I would like to represent the - after the number, like in this example:
[2, 5-, 4, 0-, 1, 6-, 2-]
Note that I can not use the usual sign because I need to be able of assigning - to 0, so that 0- is different than 0 (also, may be in the future I will need to use negative numbers, like in [-4-, -2]).
I did the easy part, which is to define the data type for the terms of the list and implement the show function.
data Term = T Int Bool deriving (Eq)
instance Show Term where
show (T v True) = show v
show (T v False) = show v ++ "-"
What I don't know is how to do the corresponding read function, or whether I cannot use the - sign, because it is a sign of the Haskell language. Suggestions are welcome.
Try something like this:
instance Read Term where
readsPrec n s = do
(i,rest) <- readsPrec (n+1) s -- read `i :: Int`
return $ case rest of -- look at the rest of the string
('-':rest') -> (T i False, rest') -- if it starts with '-'...
rest' -> (T i True, rest') -- if it doesn't...
Read in Haskell follows closely the idea that a parser can be represented by the type String -> [(a, String)] (this type is given the type synonym ReadS. To familiarize yourself with this idea of parsing, I recommend the reading the following functional pearl on monadic parsing.
Then, from GHCi:
ghci> read "[2, 5-, 4, 0-, 1, 6-, 2-]" :: [Term]
[2,5-,4,0-,1,6-,2-]
I like very much the answer of Alec, which I accepted. But after reading, thinking and trying, I reached another quite simple solution, that I would like to share here.
It uses reads instead of readsPrec because the Term constructor is not infix, so we don't need to manage precedence, and it is not monadic.
instance Read Term where
readsPrec _ s =
[(T v False, rest) | (v, '-' : rest) <- reads s] ++
[(T v True , rest) | (v, rest) <- reads s]
The symmetry with the corresponding Show instance is notable:
instance Show Term where
show (T v True) = show v
show (T v False) = show v ++ "-"

Instance read Haskell

I need to implement a read instance of the data type
data GameAction = GameAction (Int, Int) deriving (Eq)
I did this
instance Read GameAction where
readProc (x:xs:_) = setGA (read x) (read xs)
But i get the error
`readProc' is not a (visible) method of class `Read'
any idea??
Firstly, try to include more information and context in your question next time as it's helpful.
Second, it appears as if your issue is simply a typo: readProc vs. the actual readPrec method in the Read typeclass.
Third, implementing Read is not neccesary here as it can be easily derived:
data GameAction = GameAction (Int, Int) deriving (Show,Eq,Read)
And in ghci:
ghci> let x = GameAction (5,6)
ghci> (read . show) x == id x
True
So there you go.
But more importantly, why are you trying to implement a Read instance by hand? Show and Read are for encoding/decoding data types to and from String, which should only be used for debug purposes. If you want something more specialized than what the automatically derived Read instance gives you, you're probably looking for something more than what Read should be used for. If you want to parse UTF-8 strings into data types, look at combining the text library with the attoparsec library.
Thanks you all.
I could solve my problem like follow
instance Read GameAction where
readsPrec _ (x:y:rest) = let board = read [x] :: Int;
cel = read [y] :: Int;
in
if all isDigit [x,y] then
[(setGA board cel, rest)]
else []
readsPrec _ _ = []

haskell writing constructors that do work in them

i have a few questions
Im writing this constructor called rope which i have like this
data Rope = TextRope{ropeText :: String}
| ConcatRope{rope1 :: Rope, rope2 :: Rope}
| SubRope{subRopetext :: Rope, starting :: Integer, ending :: Integer}
deriving Show
First off when i make a TextRope like this
*Main> let s =TextRope "why"
*Main> s
TextRope {ropeText = "why"}
*Main>
when i do s i want to just get the string of the constructor which is why and im not really sure about that.
Also curious about concat and sub constructors. Specifically it seems like to me you are calling these two constructors there is things happening, you are returning the result of concatenating rope 1 and rope 2 together, im not sure how to describe that in this language, you are defining the data structure but somehow the return of that is a result that has to be calculated by the structure
Here are some examples of what how these functions work
> let tr = TextRope "Hello,"
> let sr = TextRope " world!"
> let hw = ConcatRope tr sr
> let ow = SubRope hw 4 4
> tr
Hello,
> sr
world!
> hw
Hello, world!
Sort of confused overall, new to haskell constructors and datatypes, so some pointers would be helpful (not c pointers though!)
Data constructors never do work. They only hold the data you pass into them. If you want work to be done, you should define what are called smart constructors, which are just functions that perform some operation before passing it to the actual constructor. An example might be
data Fraction = Fraction
{ numerator :: Int
, denominator :: Int
} deriving (Eq)
(%) :: Int -> Int -> Fraction
x % y =
let (a, b) = reduce x y
in Fraction a b
-- Reduces a fraction to it's simplest terms
reduce :: Int -> Int -> (Int, Int)
reduce num den = undefined
Here you wouldn't export the Fraction constructor from your module, just the % function that constructs one in the most reduced form.
The other problem you have is that you want your constructors to print out differently. You can achieve this by not deriving Show. However, I will warn that the Haskell convention is that show . read = read . show = id, which wouldn't hold for what you want to do. This isn't a strict convention, though, and there's nothing stopping you from doing something like:
data Rope = <your implementation minus the deriving Show bit>
instance Show Rope where
show (TextRope t) = t
show (ConcatRope r1 r2) = show r1 ++ show r2
show (SubRope r starting ending) = <exercise left to reader>
As an aside, I would recommend against having a sum type of records with different field names, this can lead to problems where your program type-checks but contains errors that can be caught at compile time if written differently. For example, what would happen if you had the code
> ropeText (ConcatRope (TextRope "Hello, ") (TextRope "world!"))
This would cause an error and crash your program! Instead, it looks like you just want a Rope type with concat and subRope functions, so you could implement it very simply as
data Rope = Rope String deriving (Eq)
concatRope :: Rope -> Rope -> Rope
concatRope (Rope r1) (Rope r2) = Rope (r1 ++ r2)
-- Why use Integer instead of Int? You might find it's easier to implement this function
subRope :: Rope -> Integer -> Integer -> Rope
subRope (Rope r) start end = Rope $ substr start end r
where substr s e text = <exercise left to reader>
Now there's absolutely no way to have an illegal rope operation, the only difference is now you have to use concatRope in place of ConcatRope and subRope in place of SubRope. You're guaranteed that these functions will do what you want, you don't have some complicated type that doesn't help you anyway.
if you don't implement your own show (not with auto-deriving) you will have a harder time getting what you want.
But if you do it's kindof easy:
data Rope = TextRope{ropeText :: String}
| ConcatRope{rope1 :: Rope, rope2 :: Rope}
| SubRope{subRopetext :: Rope, starting :: Integer, ending :: Integer}
instance Show Rope where
show (TextRope s) = s
show (ConcatRope a b) = show a ++ show b
I'm sure you'll find the implementation for the SubRope case youself ;)
Your example code and your example interactive results don't match. This is how you've defined Rope:
data Rope = TextRope{ropeText :: String}
| ConcatRope{rope1 :: Rope, rope2 :: Rope}
| SubRope{subRopetext :: Rope, starting :: Integer, ending :: Integer}
deriving Show
The deriving Show part is key there; we'll see how.
Later you show this example output:
> let tr = TextRope "Hello,"
> let sr = TextRope " world!"
> let hw = ConcatRope tr sr
> hw
Hello, world!
With the code that I just showed, actually, what you'll see is the following:
> hw
ConcatRope { rope1 = TextRope "Hello,", rope2 = TextRope " world!" }
The only way we could get the output that you describe is if we got rid of the deriving Show clause in your definition of Rope, and wrote this:
instance Show Rope where
show (TextRope text) = text
show (ConcatRope r1 r2) = show r1 ++ show r2
show (SubRope rope start end) = ...

Lens package with algebraic types

I was coding with with the lens package. Everything was going fine until I tried to access a certain field on an algebraic type:
import Control.Lens
data Type = A { _a :: Char } | B
makeLenses ''Type
test1 = _a (A 'a')
test2 = (A 'a') ^. a
No instance for (Data.Monoid.Monoid Char)
arising from a use of `a'
Possible fix:
add an instance declaration for (Data.Monoid.Monoid Char)
In the second argument of `(^.)', namely `a'
In the expression: (A 'a') ^. a
In an equation for `test2': test2 = (A 'a') ^. a
I could just go with _a, but the datatype in my real program is much deeper and I kind of intended on using lens to lower the amount of work I have to do. I have been looking over the lens library but there's so much there, and I'm not sure if he's dealt with this scenario or it is just something the lens library doesn't support.
As a side note, if I actually use a monoid like String for the datatype instead of Char, it then compiles and gives the right answer, I have no idea why.
Edit: After reading hammar's comment, I tried this and this works:
test2 = (A 'a') ^? a
test3 = B ^? a
But it is kind of weird to get a maybe out of that for something that has to exist.
Just so that this is answered, my problem was that I had an algebraic type where some fields were in common between the different constructors but there was a couple fields that weren't shared would die in runtime if I tried to use them.
data Exercise =
BarbellExercise {
name :: String,
weight :: Int,
reps :: Int
} |
BodyWeightExercise {
name :: String,
reps :: Int
}
exer1 = BarbellExercise "Squats" 235 15
exer2 = BarbellExercise "Deadlifts" 265 15
exer3 = BodyWeightExercise "Pullups" 12
exer4 = BarbellExercise "Overhead Press" 85 15
workout = [exer1, exer2, exer3, exer4]
test = do
mapM_ displayExercise workout
where
displayExercise x = putStrLn $ "Exercise: " ++ (name x) ++ " You must perform " ++ (show $ reps x) ++ "#" ++ (show $ weight x)
This compiles but dies runtime if I make the mistake of using the weight function. Understandable mistake. When lenses uses template haskell to generate instances it notices this and changes its behavior to prevent a mistake. You could remove the field accessors but in my case most of the fields were the same between datatypes. Here's how I should have written the data type once I noticed the fields did not match up:
data Exercise =
BarbellExercise
String -- ^ name
Int -- ^ reps
Int -- ^ weight
|
BodyWeightExercise
String -- ^ name
Int -- reps
name :: Exercise -> String
name (BarbellExercise n _ _) = n
name (BodyWeightExercise n _) = n
reps :: Exercise -> Int
reps (BarbellExercise _ r _) = r
reps (BodyWeightExercise _ r) = r
By doing it this way, while it is a little less clean, the error are caught at compile time. By forcing me to write the functions myself I would notice any partial functions as I was writing them.
I do kind of wish ghc would have warned me. It seems like it would be really easy for it to detect such a thing.

Haskell data serialization of some data implementing a common type class

Let's start with the following
data A = A String deriving Show
data B = B String deriving Show
class X a where
spooge :: a -> Q
[ Some implementations of X for A and B ]
Now let's say we have custom implementations of show and read, named show' and read' respectively which utilize Show as a serialization mechanism. I want show' and read' to have types
show' :: X a => a -> String
read' :: X a => String -> a
So I can do things like
f :: String -> [Q]
f d = map (\x -> spooge $ read' x) d
Where data could have been
[show' (A "foo"), show' (B "bar")]
In summary, I wanna serialize stuff of various types which share a common typeclass so I can call their separate implementations on the deserialized stuff automatically.
Now, I realize you could write some template haskell which would generate a wrapper type, like
data XWrap = AWrap A | BWrap B deriving (Show)
and serialize the wrapped type which would guarantee that the type info would be stored with it, and that we'd be able to get ourselves back at least an XWrap... but is there a better way using haskell ninja-ery?
EDIT
Okay I need to be more application specific. This is an API. Users will define their As, and Bs and fs as they see fit. I don't ever want them hacking through the rest of the code updating their XWraps, or switches or anything. The most i'm willing to compromise is one list somewhere of all the A, B, etc. in some format. Why?
Here's the application. A is "Download a file from an FTP server." B is "convert from flac to mp3". A contains username, password, port, etc. information. B contains file path information. There could be MANY As and Bs. Hundreds. As many as people are willing to compile into the program. Two was just an example. A and B are Xs, and Xs shall be called "Tickets." Q is IO (). Spooge is runTicket. I want to read the tickets off into their relevant data types and then write generic code that will runTicket on the stuff read' from the stuff on disk. At some point I have to jam type information into the serialized data.
I'd first like to stress for all our happy listeners out there that XWrap is a very good way, and a lot of the time you can write one yourself faster than writing it using Template Haskell.
You say you can get back "at least an XWrap", as if that meant you couldn't recover the types A and B from XWrap or you couldn't use your typeclass on them. Not true! You can even define
separateAB :: [XWrap] -> ([A],[B])
If you didn't want them mixed together, you should serialise them seperately!
This is nicer than haskell ninja-ery; maybe you don't need to handle arbitrary instances, maybe just the ones you made.
Do you really need your original types back? If you feel like using existential types because you just want to spooge your deserialised data, why not either serialise the Q itself, or have some intermediate data type PoisedToSpooge that you serialise, which can deserialise to give you all the data you need for a really good spooging. Why not make it an instance of X too?
You could add a method to your X class that converts to PoisedToSpooge.
You could call it something fun like toPoisedToSpooge, which trips nicely off the tongue, don't you think? :)
Anyway this would remove your typesystem complexity at the same time as resolving the annoying ambiguous type in
f d = map (\x -> spooge $ read' x) d -- oops, the type of read' x depends on the String
You can replace read' with
stringToPoisedToSpoogeToDeserialise :: String -> PoisedToSpooge -- use to deserialise
and define
f d = map (\x -> spooge $ stringToPoisedToSpoogeToDeserialise x) -- no ambiguous type
which we could of course write more succincly as
f = map (spooge.stringToPoisedToSpoogeToDeserialise)
although I recognise the irony here in suggesting making your code more succinct. :)
If what you really want is a heterogeneous list then use existential types. If you want serialization then use Cereal + ByteString. If you want dynamic typing, which is what I think your actual goal is, then use Data.Dynamic. If none of this is what you want, or you want me to expand please press the pound key.
Based on your edit, I don't see any reason a list of thunks won't work. In what way does IO () fail to represent both the operations of "Download a file from an FTP server" and "convert from flac to MP3"?
I'll assume you want to do more things with deserialised Tickets
than run them, because if not you may as well ask the user to supply a bunch of String -> IO()
or similar, nothing clever needed at all.
If so, hooray! It's not often I feel it's appropriate to recommend advanced language features like this.
class Ticketable a where
show' :: a -> String
read' :: String -> Maybe a
runTicket :: a -> IO ()
-- other useful things to do with tickets
This all hinges on the type of read'. read' :: Ticket a => String -> a isn't very useful,
because the only thing it can do with invalid data is crash.
If we change the type to read' :: Ticket a => String -> Maybe a this can allow us to read from disk and
try all the possibilities or fail altogether.
(Alternatively you could use a parser: parse :: Ticket a => String -> Maybe (a,String).)
Let's use a GADT to give us ExistentialQuantification without the syntax and with nicer error messages:
{-# LANGUAGE GADTs #-}
data Ticket where
MkTicket :: Ticketable a => a -> Ticket
showT :: Ticket -> String
showT (MkTicket a) = show' a
runT :: Ticket -> IO()
runT (MkTicket a) = runTicket a
Notice how the MkTicket contstuctor supplies the context Ticketable a for free! GADTs are great.
It would be nice to make Ticket and instance of Ticketable, but that won't work, because there would be
an ambiguous type a hidden in it. Let's take functions that read Ticketable types and make them read
Tickets.
ticketize :: Ticketable a => (String -> Maybe a) -> (String -> Maybe Ticket)
ticketize = ((.).fmap) MkTicket -- a little pointfree fun
You could use some unusual sentinel string such as
"\n-+-+-+-+-+-Ticket-+-+-+-Border-+-+-+-+-+-+-+-\n" to separate your serialised data or better, use separate files
altogether. For this example, I'll just use "\n" as the separator.
readTickets :: [String -> Maybe Ticket] -> String -> [Maybe Ticket]
readTickets readers xs = map (foldr orelse (const Nothing) readers) (lines xs)
orelse :: (a -> Maybe b) -> (a -> Maybe b) -> (a -> Maybe b)
(f `orelse` g) x = case f x of
Nothing -> g x
just_y -> just_y
Now let's get rid of the Justs and ignore the Nothings:
runAll :: [String -> Maybe Ticket] -> String -> IO ()
runAll ps xs = mapM_ runT . catMaybes $ readTickets ps xs
Let's make a trivial ticket that just prints the contents of some directory
newtype Dir = Dir {unDir :: FilePath} deriving Show
readDir xs = let (front,back) = splitAt 4 xs in
if front == "dir:" then Just $ Dir back else Nothing
instance Ticketable Dir where
show' (Dir p) = "dir:"++show p
read' = readDir
runTicket (Dir p) = doesDirectoryExist p >>= flip when
(getDirectoryContents >=> mapM_ putStrLn $ p)
and an even more trivial ticket
data HelloWorld = HelloWorld deriving Show
readHW "HelloWorld" = Just HelloWorld
readHW _ = Nothing
instance Ticketable HelloWorld where
show' HelloWorld = "HelloWorld"
read' = readHW
runTicket HelloWorld = putStrLn "Hello World!"
and then put it all together:
myreaders = [ticketize readDir,ticketize readHW]
main = runAll myreaders $ unlines ["HelloWorld",".","HelloWorld","..",",HelloWorld"]
Just use Either. Your users don't even have to wrap it themselves. You have your deserializer wrap it in the Either for you. I don't know exactly what your serialization protocol is, but I assume that you have some way to detect which kind of request, and the following example assumes the first byte distinguishes the two requests:
deserializeRequest :: IO (Either A B)
deserializeRequest = do
byte <- get1stByte
case byte of
0 -> do
...
return $ Left $ A <A's fields>
1 -> do
...
return $ Right $ B <B's fields>
Then you don't even need to type-class spooge. Just make it a function of Either A B:
spooge :: Either A B -> Q

Resources