[Haskell-cafe] Polymorphic functions over string libraries

Vlatko Basic vlatko.basic at gmail.com
Sun Oct 26 06:31:00 UTC 2014


Hi Gonzaw,

you could try switching to ClassyPrelude:


{-# LANGUAGE NoImplicitPrelude, OverloadedStrings #-}

import ClassyPrelude

-- | Just change the sig, and all typechecks
transform :: String -> String
--transform :: ByteString -> ByteString
--transform :: Text -> Text
transform s = s

xmain :: IO ()
xmain = readFile "input.txt" >>= writeFile "output.txt" . transform



You must write the signatures so the compiler knows which version to use, if it 
can't guess by itself.

The downside is that sometimes the polymorphic signatures and errors on types 
can be rather cryptic, but you'll get used to them.


(However, there are some issues when switching. Most of the issues I had were
  - about missing partial functions (like head,tail, etc.), so as a quick 
workaround you can use unsafeHead, unsafeTail, etc. until you find the time to 
make it correct (or headMay, tailMay, etc) and
  - switching from Prelude's FilePath to Filesystem's FilePath.)


Best regards,

vlatko


-------- Original Message  --------
Subject: [Haskell-cafe] Polymorphic functions over string libraries
From: gonzaw <gonzaw308 at gmail.com>
To: haskell-cafe at haskell.org
Date: 26.10.2014 02:36

> Hi.
>
> I was wondering what would be the best way to create a polymorphic function
> over any possible string library (Text, String, Bytestring, etc).
>
> For instance, imagine I have to read a file with text, transform this text
> in some way and output it to another file, or to the console.
> If I wanted to use String, I'd just do this:
> /
> transform :: String -> String
> main = readFile "input.txt" >>= writeFile "output.txt" . transform
> /
> But if I wanted to use Text instead, I'd have to use this:
> /
> import qualified Data.Text.IO as T
>
> transform :: Text -> Text
> main = T.readFile "input.txt" >>= T.writeFile "output.txt" . transform
> /
> Idem for ByteString.
>
> I was wondering if there was a way to create these computations in a generic
> way, for any kind of string library, something like this:
> /
> class StringLibrary s where:
> sReadFile :: FilePath -> IO s
> sWriteFile :: FilePath -> s -> IO ()
> ...
> /
> So then I'd just have this:
> /
> transform :: StringLibrary s => s -> s
> main = sReadFile "input.txt" >>= sWriteFile "output.txt" . transform
> /
> Now I can perform the computation I want without being tied down to a
> specific library. At times when I create some quick scripts, I find myself
> using one library (for example using String to get it finished more quickly,
> since I have less experience with the other ones), but find that it's too
> slow or has some problem that is solved by using one of the other libraries.
> Yet swapping from one to the other is more cumbersome than expected at
> times.
> In the example above, I could easily swap between them, just by forcing the
> compiler to typecheck to a specific one (for instance by changing the type
> of "transform"). Or if I wanted to, I could leave it as it is and export it
> as a library of my own.
>
> Is there a way to do something like this in Haskell, with existing
> libraries?
> In terms of using the string datatype as some sort of container of
> characters, I think there are libraries like Lens and mono-traversable that
> allow you to do stuff like this. But I'm not too familiar with them (at
> least using them in this way).
>
>
>
>
> --
> View this message in context: http://haskell.1045720.n5.nabble.com/Polymorphic-functions-over-string-libraries-tp5758630.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list