Haskell Platform Proposal: add the 'text' library

Alexander Dunlap alexander.dunlap at gmail.com
Sat Nov 6 11:41:32 EDT 2010


On Mon, Oct 11, 2010 at 1:12 PM, Malcolm Wallace <malcolm.wallace at me.com> wrote:
> I have myself in the past implemented a Text-like library as a replacement
> for the standard list-of-char representation.  (Before you ask, it is not
> publically releasable.)  The basic decision I took there was that the Char
> type does not exist - the only thing available is Text.  Another way of
> saying this, is that Char is simply the subset of all the Texts of size 1.
>  I am not suggesting that the Prelude or ByteString should take this view,
> but if you proceed to look at the type signatures of the Data.Text package
> on the basis that Char/Text are the "same" thing, then it may become clearer
> how to resolve the apparent name/type clashes below.
>
> Executive summary: most of the names/signatures turn out to be equivalent,
> with only a couple highlighted as significantly odd or worth changing.
>
> import Prelude hiding (Char)
> type Char = Text  -- At least we can pretend for a while.
>
>> text        base      bytestring     type in text (or equivalent if
>> absent)
>>
>> ---------------------------------------------------------------------------
>> break       -         breakSubstring Text -> Text -> (Text, Text)
>> breakBy     break     break          (Char -> Bool) -> Text -> (Text,
>> Text)
>
>  break       break     break          (Text -> Bool) -> Text -> (Text, Text)
>
> The breakSubstring functionality is semantically:
>    breakSubstring x = break (==x)
> although there may be a more efficient implementation.
> Proposal: rename Text.break to Text.breakSubstring, and Text.breakBy to
> Text.break.
>
>> breakEnd    -         -              Text -> Text -> (Text, Text)
>> -           -         breakEnd       (Char -> Bool) -> Text -> (Text,
>> Text)
>
>  breakEnd    -         breakEnd       (Text -> Bool) -> Text -> (Text, Text)
>
> Proposal: slightly generalise the type of Text.breakEnd.
>
>> count       -         -              Text -> Text -> Int
>> -           -         count          Char -> Text -> Int
>
>  count       -         count          Text -> Text -> Int
>
> Proposal: these are equivalent, no action.
>
>> find        -         -              Text -> Text -> [(Text, Text)]
>
> I'm afraid that, from the signature alone, I cannot guess what this function
> does.
>
>> findBy      find      find           (Char -> Bool) -> Text -> Maybe Char
>
>  find        find      find           (Text -> Bool) -> Text -> Maybe Text
>
> Proposal: rename Text.findBy to Text.find.
>
>> partitionBy partition -              (Char -> Bool) -> Text -> (Text,
>> Text)
>
>  partition   partition -              (Text -> Bool) -> Text -> (Text, Text)
>
> Proposal: these are equivalent, no action.
>
>> replicate   -         -              Int -> Text -> Text
>> -           replicate replicate      Int -> Char -> Text
>
>  replicate   replicate replicate      Int -> Text -> Text
>
> Proposal: these are equivalent, no action.
>
>> spanBy      span      span           (Char -> Bool) -> Text -> (Text,
>> Text)
>
>  span        span      span           (Text -> Bool) -> Text -> (Text, Text)
>
> Proposal: rename Text.spanBy to Text.span.
>
>> split       -         -              Text -> Text -> [Text]
>> -           -         split          Char -> Text -> [Text]
>
>  split       -         split          Text -> Text ->  [Text]
>
> Proposal: these are equivalent, no action,
>
>> splitBy     -         splitWith      (Char -> Bool) -> Text -> [Text]
>
>  splitWith   -         splitWith      (Text -> Bool) -> Text -> [Text]
>
> Proposal: these are equivalent, no action.
>
>> unfoldrN    -         -              Int -> (a -> Maybe (Char, a)) -> a ->
>> Text
>> -           -         unfoldrN       Int -> (a -> Maybe (Char, a)) -> a ->
>> (Text, Maybe a)
>
>  unfoldrN    -         unfoldrN       Int -> (a -> Maybe (Text, a)) -> a ->
> (Text, Maybe a)
>
> Proposal: slightly generalise the return type of Text.unfoldrN.
>
>> zipWith     zipWith   -              (Char -> Char -> Char) -> Text ->
>> Text -> Text
>> -           zipWith   zipWith        (Char -> Char -> a) -> Text -> Text
>> -> [a]
>
>  zipWith     zipWith   zipWith        (Text -> Text -> Text) -> Text -> Text
> -> Text
>
> Proposal: This is just a specialised version of the standard zipWith.  No
> action.
>
> The only extra function required is to lift the ordinary Char type to become
> a Text:
>
> Proposal: add    char :: Prelude.Char -> Text    if it does not already
> exist.
>
> I hope this is a useful contribution, if only to spark other ideas for how
> to resolve the impasse.
>
> Regards,
>    Malcolm
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>

I've found that the "split" library (by Brent Yorgey) offers a very
nice API for selecting between all of the different types of splitting
that may be necessary. Could that API perhaps be adapted for use with
ByteString and Text, giving a unified splitting interface for all of
the sequences in the Haskell Platform?

Alex


More information about the Libraries mailing list