{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
module Turtle.Line
  ( Line
  , lineToText
  , textToLines
  , linesToText
  , textToLine
  , unsafeTextToLine
  , NewlineForbidden(..)
  ) where
import Data.Text (Text)
import qualified Data.Text as Text
#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce
#endif
import Data.List.NonEmpty (NonEmpty(..))
import Data.String
#if __GLASGOW_HASKELL__ >= 710
#else
import Data.Monoid
#endif
import Data.Maybe
import Data.Typeable
import Control.Exception
import qualified Data.List.NonEmpty
data NewlineForbidden = NewlineForbidden
  deriving (Show, Typeable)
instance Exception NewlineForbidden
newtype Line = Line Text
  deriving (Eq, Ord, Show, Monoid)
#if __GLASGOW_HASKELL__ >= 804
instance Semigroup Line where
  (<>) = mappend
#endif
instance IsString Line where
  fromString = fromMaybe (throw NewlineForbidden) . textToLine . fromString
lineToText :: Line -> Text
lineToText (Line t) = t
textToLines :: Text -> NonEmpty Line
textToLines =
#if __GLASGOW_HASKELL__ >= 708
  Data.List.NonEmpty.fromList . coerce (Text.splitOn "\n")
#else
  Data.List.NonEmpty.fromList . map unsafeTextToLine . Text.splitOn "\n"
#endif
linesToText :: [Line] -> Text
linesToText =
#if __GLASGOW_HASKELL__ >= 708
  coerce Text.unlines
#else
  Text.unlines . map lineToText
#endif
textToLine :: Text -> Maybe Line
textToLine = fromSingleton . textToLines
  where
    fromSingleton (a :| []) = Just a
    fromSingleton  _        = Nothing
unsafeTextToLine :: Text -> Line
unsafeTextToLine = Line