Lots of ways you can do this. Here's a few.
With Text.Regex
:
import Text.Regex.TDFA -- I think this will work with the other regex backends too
getAllTextMatches ("One. Two. a 3.5 b. cde." =~ "([0-9]\\.[0-9]|[^.])+" :: AllTextMatches [] String)
-- ["One"," Two"," a 3.5 b"," cde"]
With Text.ParserCombinators.ReadP
(in base
, so no third-party libraries needed):
import Data.Char
import Text.ParserCombinators.ReadP
parseDigitsWithDecimalPoint = (\a b c -> [a,b,c]) <$> satisfy isDigit <*> char '.' <*> satisfy isDigit
parseNonDot = (:[]) <$> satisfy ('.' /=)
parseSentence = fmap concat . many $ parseDigitsWithDecimalPoint <++ parseNonDot
readP_to_S (sepBy parseSentence (char '.') <* eof) "One. Two. a 3.5 b. cde."
-- [(["One"," Two"," a 3.5 b"," cde",""],"")]
With Text.Regex.Applicative
:
import Control.Applicative.Combinators
import Data.Char
import Text.Regex.Applicative
parseDigitsWithDecimalPoint = (\a b c -> [a,b,c]) <$> psym isDigit <*> sym '.' <*> psym isDigit
parseNonDot = (:[]) <$> psym ('.' /=)
parseSentence = fmap concat . many $ parseDigitsWithDecimalPoint <|> parseNonDot
match (sepBy parseSentence (sym '.')) "One. Two. a 3.5 b. cde."
-- Just ["One"," Two"," a 3.5 b"," cde",""]
With Text.Megaparsec
:
{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
import Data.Char
import Text.Megaparsec
parseDigitsWithDecimalPoint = (\a b c -> [a,b,c]) <$> satisfy isDigit <*> single '.' <*> satisfy isDigit
parseNonDot = (:[]) <$> anySingleBut '.'
parseSentence = fmap concat . many $ try parseDigitsWithDecimalPoint <|> parseNonDot
parseMaybe (sepBy parseSentence (single '.')) "One. Two. a 3.5 b. cde."
-- Just ["One"," Two"," a 3.5 b"," cde",""]
Completely by hand:
import Data.Char
import Data.List.NonEmpty
foo = go id where
go f "" = f "" :| []
go f ('.':xs) = f "" <| go id xs
go f (x1:'.':x2:xs) | isDigit x1 && isDigit x2 = go (f . (x1:) . ('.':) . (x2:)) xs
go f (x:xs) = go (f . (x:)) xs
foo "One. Two. a 3.5 b. cde."
-- "One" :| [" Two"," a 3.5 b"," cde",""]