Probably a silly question but I can't for the life of me figure this out.
I want to append to the end of a list based on a series of if statements.
In python (or most other languages I am familiar with) I could do something like this:
x = ["hi"]
if True:
x.append("hello")
if not True:
x.append("wait a minute...")
if True:
x.append("goodbye")
Which would give me:
['hi', 'hello', 'goodbye']
How does one achieve such a thing in Haskell?
I can get as far as:
res :: [[Char]]
res =
let x = ["Hi"]
in
if (True)
then x ++ ["hello"]
... what goes here???
else x
Or am I going about this totally wrong?
I am very new to Haskell so please don't bite...
Idiomatically,
x = concat [ [ "hi" ],
[ "hello" | True ],
[ "wait a minute..." | not True ],
[ "goodbye" | True ] ]
In Haskell every if expression must have an else clause. In that regard it's similar to the Python conditional operator:
a if test else b
In Haskell it would be written as:
if test then a else b
So how do you write the following in Haskell?
x = ["hi"]
if True:
x.append("hello")
You would do something like:
let x = ["hi"] in
if True then x ++ ["hello"] else x
See the else clause? It just returns the value as is.
However writing code like this sucks. We want to write code like in Python, and Python is stateful. The variable x is the state. In Haskell we have the State monad for writing code like that. Consider:
import Control.Monad.State
append a = modify (++ [a])
foo :: [String] -> [String]
foo = execState $ do
when True $ append "hello"
when (not True) $ append "wait a minute..."
when True $ append "goodbye"
x = ["hi"]
res = foo x
main = print res
Simple right?
In addition to #AaditMShah's answer, if you only want to append to a value, without other modifications, the writer monad would be the proper abstraction:
import Control.Monad
import Control.Monad.Writer
append :: a -> Writer [a] ()
append = tell . (: [])
x :: [String]
x = execWriter $ do
tell ["hi"]
when True $
append "hello"
when (not True) $
append "wait a minute..."
when True $
append "goodbye"
Haskell is different than the way it is done in Python or other languages:
List (and most other data structures) are immutable.
if else is an expression in Haskell as opposed to statement which is seen in other languages. You cannot ignore the else part in Haskell like what you did with Python.
Looking at your python code, it seems what you want to do is that if the condition is True, then you want to append an element to the list. That pattern can be abstracted in the following function:
appendIfTrue :: Bool -> a -> [a] -> [a]
appendIfTrue b x xs = if b
then xs ++ [x]
else xs
Once you have written the function you can achieve the same functionality using the following code:
x = ["hi"]
main = do
let x1 = appendIfTrue True "hello" x
x2 = appendIfTrue False "wait a minute" x1
x3 = appendIfTrue True "goodbye" x2
print x3
The thing to note here that is you are creating a new list here instead of modifying them as you did in your Python code.
Demo:
λ> main
["hi","hello","goodbye"]
You need to understand that in Haskell you cannot just modify x as in your python example. You need to thread a value (a list of Strings) though your conditionals, where each step appends or does not append another String. So you can't get away with nested if-then-else statement alone. You need access to the intermediate List of Strings built so far.
So the elementary operation is to append or not append a String to a List of Strings based on a boolean. A function which does this kind of conditionall appending could look like:
condAppend :: Bool -> String -> [String] -> [String]
condAppend c suff pref = if c then pref ++ [suff]
else pref
No you just have to chain a series of condAppends and apply it to an inial List of Strings:
res = condAppend True "goodby"
$ condAppend False "wait a minute"
$ condAppend True "hello" ["Hi"]
This gives you:
["Hi","hello","goodby"]
Note that the order of execution in res is bottom to top (or right to left if you write it all in one line) or inside-out if you like as as in f (g (h x)) where the leftmost function f is applied last.
If you don't like that, you need an alternative to ($) which operates left to right. You can write your own function (>>>) as in
res'= (
condAppend True "hello"
>>>
condAppend False "wait a minute"
>>>
condAppend True "goodbye"
) ["Hi"]
where
f >>> g = g . f
and it so happens that (a much generalized version of) (>>>) is already defined in Control.Arrow.
Related
Why is this function allowed:
-- function 1
myfunc :: String
myfunc = do
x <- (return True)
show x
and this is not:
-- function 2
myfunc :: String
myfunc = do
x <- getLine
show x
The compile error:
Couldn't match type `[]' with `IO'
Expected type: IO Char
Actual type: String
I get why function 2 shouldn't work, but why then thus function 1 work?
and why does this then work:
-- function 3
myfunc = do
x <- getLine
return (show x)
I get that it returns IO String then, but why is function 1 also not forced to do this?
In function1 the do block in myfunc is working in the list monad, because String is really just [Char]. In there, return True just creates [True]. When you do x <- return True that "extracts" True out of [True] and binds it to x. The next line show x converts True into a String "True". which being the return value the compiler value expects to see, ends up working fine.
Meanwhile in function2, the do block in myfunc is also working on the list monad (for the same reason, String being really [Char]) but calls on getLine which is only available in the IO monad. So unsurprisingly, this fails.
-- EDIT 1
OP has added a function3
-- function 3
myfunc :: String
myfunc = do
x <- getLine
return (show x)
No this should not work for the same reason function2 fails.
-- EDIT 2
OP has updated function3 to fix a copy paste error.
-- function 3
myfunc = do
x <- getLine
return (show x)
This is mentioned in the comments, but for clarity sake, this works because, when the type information is unspecified, GHC makes it best inference and after seeing getLine, it figures it’s IO String which does provide getLine.
Note - I wrote this answer with as casual a tone as I could manage without being wrong with the intention of making it approachable to a beginner level.
do blocks work in the context of an arbitrary Monad. The Monad, in this case, is []. The Monad instance for lists is based on list comprehensions:
instance Monad [] where
return x = [x]
xs >>= f = [y | x <- xs, y <- f x]
You can desugar the do notation thus:
myfunc :: String
myfunc = do
x <- (return True)
show x
-- ==>
myfunc = [y | x <- return True, y <- show x]
-- ==>
myfunc = [y | x <- [True], y <- show x]
In a list comprehension, x <- [True] is really just the same as let x = True, because you're only drawing one element from the list. So
myfunc = [y | y <- show True]
Of course, "the list of all y such that y is in show True" is just show True.
I want to write a program in Haskell which will take command line arguments. For example: to print the sum of the first 6 elements of the series (which will be calculated by another function), I will write:
sum 6
and the correct answer should be displayed. I have to do this for another 5-7 different commands by checking the command line. How should I do it? Is switch case a good idea? If so, can anyone tell me how it can be done.
SOLUTION:
main = do
--Get some input
f <- getLine
--Split the input into 2 strings; one is COMMAND field and other is the ARGUMENT field using the condition the there is one space between them
let cmd = takeWhile (/=' ') f
let arg = dropWhile (/=' ') f
let val = tail arg
let p = read val::Int
--Check for the COMMAND
case cmd of
"SUM" -> if (empty arg) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (check val) then print (sum1 p) else do { putStrLn "ERR"; exitWith ExitSuccess}
"NTH" -> if (empty arg) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (check val) then print (fact p) else do { putStrLn "ERR"; exitWith ExitSuccess}
"BOUNDS" -> if (empty arg) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (check val == False) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (p > 1) then do { print c; print d} else do { putStrLn"ERR"; exitWith ExitSuccess}
"QUIT" -> if (empty arg) then exitWith ExitSuccess else do { putStrLn "ERR"; exitWith ExitSuccess}
_ -> do { putStrLn "ERR"; exitWith ExitSuccess}
--Repeat main until QUIT
main
optparse-applicative is one example of a library which supports this kind of sub-command parsing.
Let's say your program has two commands for now, "sum" and "mean". We can represent the command and its arguments using an algebraic data type, here called Command.
import Data.Monoid (mconcat)
import Options.Applicative
data Command = Sum Integer
| Mean Integer
-- et cetera
We can build a parser which accepts all of the commands, by writing parsers for each individual command, and composing them.
parseNumber :: Parser Integer
parseNumber = argument auto (metavar "N")
sumParser :: ParserInfo Command
sumParser = info (Sum <$> parseNumber)
(progDesc "Sum first N elements in series")
meanParser :: ParserInfo Command
meanParser = info (Mean <$> parseNumber)
(progDesc "Mean of first N elements in series")
commandParser :: ParserInfo Command
commandParser = info commands $ progDesc "My program" where
commands = subparser $ mconcat [
command "sum" sumParser
, command "mean" meanParser
]
If you are wondering what Parser and ParserInfo are about: Usually we build a Parser, then put it into a ParserInfo, using the info combinator to decorate it with additional information about how it should be run (for example, with progDesc). Parsers may be composed with other Parsers, typically using the applicative combinators, but a ParserInfo is only a Functor, as it represents the entry point to the program.
Since each command is like a little sub-program, we need a ParserInfo for each one. The command and subparser combinators let us take some ParserInfos and wrap them up in a Parser, turning multiple entry points into one.
Once we have a result from the parser, we can dispatch to the appropriate routine by pattern matching on the result.
main :: IO ()
main = do
cmd <- execParser commandParser
case cmd of
Sum n -> return () -- TODO perform sum command
Mean n -> return () -- TODO perform mean command
Of course, if you have the time and the need, is much better to use a command line parser library than a switch case. A proper parser gives you the ability to have flags in any order, automatic documenation etc ... Although if you don't need any of this now, you might need it later.
However, pattern matching allows you check value(s) within a list, but although the size of the list, and this at the same time. This makes writing poor man command line parsing dead-easy in Haskell.
Example
main = do
args <- getArg
case args of
["command1", a, b] -> command1 a b -- 2 argument
["command2", a ] -> command2 a -- 1 argument
"command3":as -> command3 as -- n arguments
otherwise -> putStrLn "Please read the code to see which arguments are acceptable :-)"
So even though I would propably recommend using a parsing library, if you only need a couple of options without flags , and don't have time to learn/choose one, a simple case ... of is pretty neat and much quicker/simpler to write.
You can write your own simple applicative-style parser in just a few lines. The idea is: accept a list of string pairs, where the first string is an option name and the second string is an option value, lookup for a current option name, and if it's found, treat the associated value somehow and delete the pair from the list. If it's not found, return Nothing. So Parser is defined like this:
type Parser = StateT [(String, String)] Maybe
And here is the main function:
option :: (String -> Maybe a) -> String -> Parser a
option f str = StateT $ \xs -> do
(v, xs') <- lookupDelete str xs
v' <- f v
return (v', xs')
where lookupDelete does what it says. Actual option parsers are:
sopt :: String -> Parser String
sopt = option Just
opt :: Read a => String -> Parser a
opt = option $ reads >>> listToMaybe >=> finish
finish (x, []) = Just x
finish _ = Nothing
The opt parser tries to read a string, and it succeeds if the string is read fully.
optPairs [] = Just []
optPairs (('-':'-':name):opt:xs) = ((name, opt) :) <$> optPairs xs
optPairs _ = Nothing
This function splits input into pairs. And lastly
parse :: Parser a -> String -> Maybe a
parse p = words >>> optPairs >=> runStateT p >=> finish
Here is an example:
data SubCommand = SubCommand String (Double, Double)
deriving (Show)
data Command = Sum [Integer]
| Sub SubCommand
deriving (Show)
subcommandParser :: Parser SubCommand
subcommandParser = SubCommand <$> sopt "str" <*> opt "dbls"
commandParser :: Parser Command
commandParser = Sum <$> opt "sum" <|> Sub <$> subcommandParser
main = mapM_ (print . parse commandParser)
[ "--sum [1,2,3,4]"
, "--str option --dbls (2.2,0)"
, "--dbls (2.2,0) --str option"
, "--smth smth"
]
Results in
Just (Sum [1,2,3,4])
Just (Sub (SubCommand "option" (2.2,0.0)))
Just (Sub (SubCommand "option" (2.2,0.0)))
Nothing
The whole code: http://lpaste.net/114365
I use System.Random and System.Random.Shuffle to shuffle the order of characters in a string, I shuffle it using:
shuffle' string (length string) g
g being a getStdGen.
Now the problem is that the shuffle can result in an order that's identical to the original order, resulting in a string that isn't really shuffled, so when this happens I want to just shuffle it recursively until it hits a a shuffled string that's not the original string (which should usually happen on the first or second try), but this means I need to create a new random number generator on each recursion so it wont just shuffle it exactly the same way every time.
But how do I do that? Defining a
newg = newStdGen
in "where", and using it results in:
Jumble.hs:20:14:
Could not deduce (RandomGen (IO StdGen))
arising from a use of shuffle'
from the context (Eq a)
bound by the inferred type of
shuffleString :: Eq a => IO StdGen -> [a] -> [a]
at Jumble.hs:(15,1)-(22,18)
Possible fix:
add an instance declaration for (RandomGen (IO StdGen))
In the expression: shuffle' string (length string) g
In an equation for `shuffled':
shuffled = shuffle' string (length string) g
In an equation for `shuffleString':
shuffleString g string
= if shuffled == original then
shuffleString newg shuffled
else
shuffled
where
shuffled = shuffle' string (length string) g
original = string
newg = newStdGen
Jumble.hs:38:30:
Couldn't match expected type `IO StdGen' with actual type `StdGen'
In the first argument of `jumble', namely `g'
In the first argument of `map', namely `(jumble g)'
In the expression: (map (jumble g) word_list)
I'm very new to Haskell and functional programming in general and have only learned the basics, one thing that might be relevant which I don't know yet is the difference between "x = value", "x <- value", and "let x = value".
Complete code:
import System.Random
import System.Random.Shuffle
middle :: [Char] -> [Char]
middle word
| length word >= 4 = (init (tail word))
| otherwise = word
shuffleString g string =
if shuffled == original
then shuffleString g shuffled
else shuffled
where
shuffled = shuffle' string (length string) g
original = string
jumble g word
| length word >= 4 = h ++ m ++ l
| otherwise = word
where
h = [(head word)]
m = (shuffleString g (middle word))
l = [(last word)]
main = do
g <- getStdGen
putStrLn "Hello, what would you like to jumble?"
text <- getLine
-- let text = "Example text"
let word_list = words text
let jumbled = (map (jumble g) word_list)
let output = unwords jumbled
putStrLn output
This is pretty simple, you know that g has type StdGen, which is an instance of the RandomGen typeclass. The RandomGen typeclass has the functions next :: g -> (Int, g), genRange :: g -> (Int, Int), and split :: g -> (g, g). Two of these functions return a new random generator, namely next and split. For your purposes, you can use either quite easily to get a new generator, but I would just recommend using next for simplicity. You could rewrite your shuffleString function to something like
shuffleString :: RandomGen g => g -> String -> String
shuffleString g string =
if shuffled == original
then shuffleString (snd $ next g) shuffled
else shuffled
where
shuffled = shuffle' string (length string) g
original = string
End of answer to this question
One thing that might be relevant which I don't know yet is the difference between "x = value", "x <- value", and "let x = value".
These three different forms of assignment are used in different contexts. At the top level of your code, you can define functions and values using the simple x = value syntax. These statements are not being "executed" inside any context other than the current module, and most people would find it pedantic to have to write
module Main where
let main :: IO ()
main = do
putStrLn "Hello, World"
putStrLn "Exiting now"
since there isn't any ambiguity at this level. It also helps to delimit this context since it is only at the top level that you can declare data types, type aliases, and type classes, these can not be declared inside functions.
The second form, let x = value, actually comes in two variants, the let x = value in <expr> inside pure functions, and simply let x = value inside monadic functions (do notation). For example:
myFunc :: Int -> Int
myFunc x =
let y = x + 2
z = y * y
in z * z
Lets you store intermediate results, so you get a faster execution than
myFuncBad :: Int -> Int
myFuncBad x = (x + 2) * (x + 2) * (x + 2) * (x + 2)
But the former is also equivalent to
myFunc :: Int -> Int
myFunc x = z * z
where
y = x + 2
z = y * y
There are subtle difference between let ... in ... and where ..., but you don't need to worry about it at this point, other than the following is only possible using let ... in ..., not where ...:
myFunc x = (\y -> let z = y * y in z * z) (x + 2)
The let ... syntax (without the in ...) is used only in monadic do notation to perform much the same purpose, but usually using values bound inside it:
something :: IO Int
something = do
putStr "Enter an int: "
x <- getLine
let y = myFunc (read x)
return (y * y)
This simply allows y to be available to all proceeding statements in the function, and the in ... part is not needed because it's not ambiguous at this point.
The final form of x <- value is used especially in monadic do notation, and is specifically for extracting a value out of its monadic context. That may sound complicated, so here's a simple example. Take the function getLine. It has the type IO String, meaning it performs an IO action that returns a String. The types IO String and String are not the same, you can't call length getLine, because length doesn't work for IO String, but it does for String. However, we frequently want that String value inside the IO context, without having to worry about it being wrapped in the IO monad. This is what the <- is for. In this function
main = do
line <- getLine
print (length line)
getLine still has the type IO String, but line now has the type String, and can be fed into functions that expect a String. Whenever you see x <- something, the something is a monadic context, and x is the value being extracted from that context.
So why does Haskell have so many different ways of defining values? It all comes down to its type system, which tries really hard to ensure that you can't accidentally launch the missiles, or corrupt a file system, or do something you didn't really intend to do. It also helps to visually separate what is an action, and what is a computation in source code, so that at a glance you can tell if an action is being performed or not. It does take a while to get used to, and there are probably valid arguments that it could be simplified, but changing anything would also break backwards compatibility.
And that concludes today's episode of Way Too Much Information(tm)
(Note: To other readers, if I've said something incorrect or potentially misleading, please feel free to edit or leave a comment pointing out the mistake. I don't pretend to be perfect in my descriptions of Haskell syntax.)
I would like to obfuscate a text file report without obscuring certain keywords, like report titles, column headers, etc. I've built such a program using newLisp. I'm trying to implement the functionality in Haskell from scratch. Here is the code I've got so far, which compiles and runs successfully for the case of simple obfuscation.
module Main where
import Data.Char (isAlpha, isNumber, isUpper, toUpper)
import System.Environment (getArgs)
import System.Random (getStdGen, randomR, StdGen)
helpMessage = [ "Usage: cat filename(s) | obfuscate [-x filename] > filename",
"",
"Obfuscates text files. This obliterates the text--there is no recovery. This",
"is not encryption. It's simple, if slow, obfuscation.",
"",
"To include a list of words not to obfuscate, use the -x option. List one word",
"per line in the file.",
"" ]
data CLOpts = CLOpts { help :: Bool
, exceptionFileP :: Bool
, exceptionFile :: String }
main = do
args <- getArgs
if length args > 0
then do let opts = parseCL args CLOpts { help=False, exceptionFileP=False, exceptionFile="" }
if help opts
then do putStrLn $ unlines helpMessage
else do if exceptionFileP opts
then do exceptions <- readFile $ exceptionFile opts
obf complexObfuscation $ lines exceptions
else do obf simpleObfuscation []
else do obf simpleObfuscation []
where obf f xs = do
g <- getStdGen
c <- getContents
putStrLn $ f xs g c
parseCL :: [String] -> CLOpts -> CLOpts
parseCL [] opts = opts
parseCL ("-x":f:xs) opts = parseCL xs opts { exceptionFileP=True, exceptionFile=f }
parseCL (_:xs) opts = parseCL xs opts { help=True }
simpleObfuscation xs = obfuscate
complexObfuscation exceptions g c = undefined
obfuscate :: StdGen -> String -> String
obfuscate g = obfuscate' g []
where
obfuscate' _ a [] = reverse a
obfuscate' g a text#(c:cs)
| isAlpha c = obf obfuscateAlpha g a text
| isNumber c = obf obfuscateDigit g a text
| otherwise = obf id g a text
obf f g a (c:cs) = let (x,g') = f (c,g) in obfuscate' g' (x:a) cs
obfuscateAlpha, obfuscateDigit :: (Char, StdGen) -> (Char, StdGen)
obfuscateAlpha (c,g) = obfuscateChar g range
where range
| isUpper c = ('A','Z')
| otherwise = ('a','z')
obfuscateDigit (c,g) = obfuscateChar g ('0','9')
obfuscateChar :: StdGen -> (Char, Char) -> (Char, StdGen)
obfuscateChar = flip randomR
I cannot get my head around how to obfuscate all text except words passed in as exceptions. My newLisp implementation relied on it's built-in regular expression handling. I've not had much luck using regular expressions in Haskell. Probably old libraries or something.
I've tried splitting the text up into lines and words and creating what in J would be called a fret. That approach is quickly getting unwieldy. I tried to use a parser, but I think that's going to get pretty hairy, too.
Does anyone have suggestion(s) on a simple, straight-forward approach to identifying exception words in the text and how not to send those to the obfuscate function? Haskell is such a brilliant language, surely I'm missing something right under my nose.
I tried Google, but it seems my desire for providing an exception list of words not to obfuscate is novel. Otherwise, obfuscation is quite simple.
Update
Following the idea I marked as the answer, I created my own words function:
words' :: String -> [String]
words' text = f text [] []
where f [] wa ta = reverse $ wa:ta
f (c:cs) wa ta =
if isAlphaNum c
then f cs (c:wa) ta
else f cs [] $ if length wa > 0 then [c]:(reverse wa):ta else [c]:ta
Using break didn't work. I think mutual recursion with break and span would have worked, but I went with the code above before I thought of trying that.
Then I implemented complexObfuscation as follows:
complexObfuscation exceptions g = unlines . map obfuscateLine . lines
where obfuscateLine = concatMap obfuscateWord . words'
obfuscateWord word =
if word `elem` exceptions
then word
else obfuscate g word
This accomplished what I was after. Unfortunately, I did not anticipate that the same generator would generate the same characters with every call to obfuscate. So each word starts with the same characters. Lol. A problem for another day.
Read the exceptions file and build a Data.Set.Set.
After splitting the input file into lines, split it further into words.
Then, obfuscate each word individually. If a word is an element of the Set you built before, leave it as it is. Otherwise, apply your obfuscate function to each character.
I don't understand this type error:
Couldn't match expected type `[t0]' with actual type `IO ()'
In the return type of a call of `printv'
In a stmt of a 'do' expression: px <- printv x
In the expression:
do { px <- printv x;
sep <- print ", ";
rest <- prints xs;
return (px : sep : rest) }
From:
data Value = IntValue Int
| TruthValue Bool
deriving (Eq, Show)
printv :: Value -> IO()
printv (IntValue i) = print i
printv (TruthValue b) = print ("boolean" ++ show b)
prints :: [Value] -> [IO()]
prints [] = []
prints (x:xs) = do px <- printv x
sep <- print ", "
rest <- prints xs
return (px:sep:rest)
It looks to me like every element (px) is converted into an IO() action, and then that is added to a list of the same things, thus producing an [IO()] list.
What am I missing here? Converting it to a list of strings, by removing the print's, works fine.
You're missing the return on the [] case of prints:
prints [] = return []
However, your prints is very strange. It returns a [()], because print is outputting strings to the console, not returning them.
Do you mean to return strings from your printv function?
Since you're trying to pretty print a syntax tree, here's roughly the right way to do it:
Use pretty-printing combinators
Use a pretty typeclass
Like so:
import Text.PrettyPrint
import Data.List
data Value
= VInt Int
| VBool Bool
deriving (Eq, Show)
class Pretty a where
pretty :: a -> Doc
instance Pretty Value where
pretty (VInt i) = int i
pretty (VBool b) = text "Boolean" <+> text (show b)
draw :: [Value] -> String
draw = intercalate ", " . map (render.pretty)
main = putStrLn $ draw [VInt 7, VBool True, VInt 42]
Running it:
*A> main
7, Boolean True, 42
Take a closer look at the type of your function:
prints :: [Value] -> [IO()]
But if we now take a look at prints [] = [], this can't match, because the type of that one is
prints :: [t] -> [a]
Therefore, you missed using prints [] = return [], to make it work.
If you're not evaluating an IO action, you don't need a do block. Just treat IO () as a normal type.
prints (x:xs) = printv x : print ", " : prints xs
You don't want prints to return an array of IO actions. You want it to return a single IO action that represents each of the IO actions bound together. Something like:
prints xs = mapM_ (\x -> printv x >> putStr ", ") xs
Except that I don't think the new lines are going to end up where you want them.
Look at the documentation for mapM and sequence for more information. In particular, the implementation of sequence is probably similar to what you're trying to do.
However, I would really recommend that instead doing all the work in an IO function, you should write a pure function to render the textual format you want, and then just print that. In particular, it seems that an instance of Show for Value would be appropriate.
instance Show Value where
show (IntValue i) = show i
show (TruthValue b) = "boolean " ++ show b
That way you can just call print value rather than printv value, and if you really wanted to you could define prints as follows.
import Data.List
prints :: (Show a) => [a] -> IO ()
prints = putStrLn . intercalate ", " . map show`.