<div dir="ltr">The trick with ClassyPrelude is to use the system-fileio package instead of straight directory. With that in place, you get:<br><div><br></div><div><div>{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-}</div><div>import ClassyPrelude</div><div>import Data.Aeson</div><div>import Filesystem (listDirectory)</div><div><br></div><div>data Product = Product</div><div>    { image :: Text</div><div>    , description  :: Text</div><div>    } deriving Show</div><div><br></div><div>instance ToJSON Product where</div><div>    toJSON (Product image description) = object ["image" .= image, "description" .= description]</div><div><br></div><div><br></div><div>encodeToJson :: FilePath -> IO()</div><div>encodeToJson srcName = do</div><div>    let jsonName = basename srcName <.> "json"</div><div>    contents <- readFile srcName</div><div>    let contentLines = lines contents</div><div>    case contentLines of  -- head is unsafe!  try your code on an empty file</div><div>      (firstLine : restLines) -> writeFile jsonName (encode Product {</div><div>            image = firstLine,</div><div>            description = unlines restLines</div><div>            })</div><div>      _ -> print ("error: invalid source file: " ++ srcName)</div><div><br></div><div><br></div><div>main = do</div><div>    names <- listDirectory "."</div><div>    let srcNames = filter (flip hasExtension "src") names</div><div>    mapM_ encodeToJson srcNames</div></div><div><br></div></div><br><div class="gmail_quote">On Sun, Mar 1, 2015 at 6:47 PM Bram Neijt <<a href="mailto:bneijt@gmail.com">bneijt@gmail.com</a>> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Thank you all for the responses.<br>
<br>
Qualified imports for a script of less then a page make the code less<br>
readable. That is why I want to specifically import subsets of<br>
functions and not prefix everything with qualified imports.<br>
<br>
I've taken the code from Travis (clean up some of the useless<br>
pack/unpack), decided to use "NoImplicitPrelude" and then I had this:<br>
<br>
#!/usr/bin/runghc<br>
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-}<br>
import Prelude (Show, IO, (++), print, String, filter)<br>
import Data.List (isSuffixOf)<br>
import Data.Text hiding (isSuffixOf, filter)<br>
import <a href="http://Data.Text.IO" target="_blank">Data.Text.IO</a><br>
import Control.Monad (mapM_)<br>
<br>
import qualified Data.ByteString.Lazy as BL<br>
import System.Directory (getDirectoryContents)<br>
import System.FilePath.Posix ((<.>), FilePath, takeBaseName)<br>
<br>
import Data.Aeson<br>
<br>
data Product = Product<br>
    { image :: Text<br>
    , description  :: Text<br>
    } deriving Show<br>
<br>
instance ToJSON Product where<br>
    toJSON (Product image description) = object ["image" .= image,<br>
"description" .= description]<br>
<br>
<br>
encodeToJson :: FilePath -> IO()<br>
encodeToJson srcName = do<br>
    let jsonName = takeBaseName srcName <.> "json"<br>
    contents <- readFile srcName<br>
    let contentLines = lines contents<br>
    case contentLines of  -- head is unsafe!  try your code on an empty file<br>
      (firstLine : restLines) -> BL.writeFile jsonName (encode Product {<br>
            image = firstLine,<br>
            description = unlines restLines<br>
            })<br>
      _ -> print ("error: invalid source file: " ++ srcName)<br>
<br>
<br>
main = do<br>
    names <- getDirectoryContents "."<br>
    let srcNames = filter (isSuffixOf ".src") names<br>
    mapM_ encodeToJson srcNames<br>
<br>
<br>
What bugs me is that this is a really simple thing to do in any other<br>
language, but here I seem to be stuck between Prelude and Text and as<br>
a beginner Prelude is king.<br>
<br>
I tried ClassyPrelude but got stuck at not being able to get the<br>
result of getDirectoryContents into the ClassyPrelude version of<br>
mapM_. Sorry but I gave up on that.<br>
<br>
I think that given all this, the above code is as beautiful as Haskell<br>
can pull this off at the moment.<br>
<br>
If somebody can prove me wrong, I would love to still see it.<br>
<br>
Greetings,<br>
<br>
Bram<br>
<br>
<br>
<br>
<br>
On Sun, Mar 1, 2015 at 1:42 AM, Travis Cardwell<br>
<<a href="mailto:travis.cardwell@extellisys.com" target="_blank">travis.cardwell@extellisys.<u></u>com</a>> wrote:<br>
> On 2015年02月28日 20:23, Bram Neijt wrote:<br>
>> It quickly became a collection of "import qualified" and "T.unpack,<br>
>> T.pack" calls that made the whole thing look ugly [1].<br>
> <SNIP><br>
>> [1] Source can be read here: <a href="https://gist.github.com/bneijt/9bdb4b1759790a8463c9" target="_blank">https://gist.github.com/<u></u>bneijt/9bdb4b1759790a8463c9</a><br>
><br>
> File paths are of type `System.FilePath.Posix.<u></u>FilePath`, a type alias for<br>
> `String`.  Note that this convention is also followed in `ByteString` and<br>
> `Text` libraries; they do not use `ByteString` or `Text` types for the<br>
> file paths.<br>
><br>
> In this code, file paths are packed only to have to unpack them again<br>
> (twice!), which likely offsets any performance improvements of using the<br>
> `Text` version of `isSuffixOf`.<br>
><br>
> Here is a version using the same style but without packing file paths:<br>
> <a href="https://gist.github.com/TravisCardwell/fd9981e4968e4af3751d" target="_blank">https://gist.github.com/<u></u>TravisCardwell/<u></u>fd9981e4968e4af3751d</a><br>
><br>
> I included a few other changes, which are commented in the code.<br>
><br>
> By the way, I do not think that qualified imports are bad.  I like them<br>
> because they provide an explicit reference to the source module of a function.<br>
><br>
> Cheers,<br>
><br>
> Travis<br>
> ______________________________<u></u>_________________<br>
> Haskell-Cafe mailing list<br>
> <a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" target="_blank">http://mail.haskell.org/cgi-<u></u>bin/mailman/listinfo/haskell-<u></u>cafe</a><br>
______________________________<u></u>_________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" target="_blank">http://mail.haskell.org/cgi-<u></u>bin/mailman/listinfo/haskell-<u></u>cafe</a><br>
</blockquote></div>