{-# LANGUAGE UnicodeSyntax, Safe #-} module Data.InfList.InfString ( InfString , toString -- InfString → String , showInfString -- InfString → String , lines -- InfString → InfList String , unlines -- InfList String → InfString , words -- InfString → InfList String , unwords -- InfList String → InfString ) where import Prelude hiding (dropWhile, break, lines, unlines, words, unwords) import Data.InfList import qualified Data.Char (isSpace) -- | Analogous to the 'String' data type. type InfString = InfList Char -- | Convert an 'InfString' to the equivalent infinite 'String'. toString :: InfString -- ^ An 'InfString' to convert → String -- ^ the equivalent 'String' toString = toList -- | Declaring 'InfString' an instance of 'Show' results in overlapping -- typeclasses. We instead use a simple function that converts an 'InfString' -- to an infinite 'String'. showInfString :: InfString -- ^ The 'InfString' to convert → String -- ^ its 'String' representation showInfString = ("InfString "++) . show . toList -- | Split an 'InfString' into an infinite list of lines. lines :: InfString -- ^ The string to split → InfList String -- ^ The string split into lines lines s = line:::lines rest where (line, _:::rest) = break (=='\n') s -- | Join an infinite list of lines into an infinite string. unlines :: InfList String -- ^ A list of lines → InfString -- ^ The joined string unlines (l:::ls) = l +++ ('\n' ::: unlines ls) -- | Split an infinite string by whitespace. words :: InfString -- ^ A string to split into words → InfList String -- ^ A list of words from the string words s = word:::restWords where (word, _:::restChars) = break Data.Char.isSpace s restWords = words $ dropWhile Data.Char.isSpace restChars -- | Join an infinite list of words into an infinite string. -- A space is inserted between each word. unwords :: InfList String -- ^ A list of words → InfString -- ^ The words joined by spaces unwords (w:::ws) = w +++ (' ' ::: unwords ws)