1{-# LANGUAGE CPP #-}
2{-# LANGUAGE DeriveDataTypeable #-}
3{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4{-# LANGUAGE OverloadedStrings #-}
5
6module Turtle.Line
7 ( Line
8 , lineToText
9 , textToLines
10 , linesToText
11 , textToLine
12 , unsafeTextToLine
13 , NewlineForbidden(..)
14 ) where
15
16import Data.Text (Text)
17import qualified Data.Text as Text
18#if __GLASGOW_HASKELL__ >= 708
19import Data.Coerce
20#endif
21import Data.List.NonEmpty (NonEmpty(..))
22import Data.String
23#if __GLASGOW_HASKELL__ >= 710
24#else
25import Data.Monoid
26#endif
27import Data.Maybe
28import Data.Typeable
29import Control.Exception
30
31import qualified Data.List.NonEmpty
32
33-- | The `NewlineForbidden` exception is thrown when you construct a `Line`
34-- using an overloaded string literal or by calling `fromString` explicitly
35-- and the supplied string contains newlines. This is a programming error to
36-- do so: if you aren't sure that the input string is newline-free, do not
37-- rely on the @`IsString` `Line`@ instance.
38--
39-- When debugging, it might be useful to look for implicit invocations of
40-- `fromString` for `Line`:
41--
42-- > >>> sh (do { line <- "Hello\nWorld"; echo line })
43-- > *** Exception: NewlineForbidden
44--
45-- In the above example, `echo` expects its argument to be a `Line`, thus
46-- @line :: `Line`@. Since we bind @line@ in `Shell`, the string literal
47-- @\"Hello\\nWorld\"@ has type @`Shell` `Line`@. The
48-- @`IsString` (`Shell` `Line`)@ instance delegates the construction of a
49-- `Line` to the @`IsString` `Line`@ instance, where the exception is thrown.
50--
51-- To fix the problem, use `textToLines`:
52--
53-- > >>> sh (do { line <- select (textToLines "Hello\nWorld"); echo line })
54-- > Hello
55-- > World
56data NewlineForbidden = NewlineForbidden
57 deriving (Show, Typeable)
58
59instance Exception NewlineForbidden
60
61-- | A line of text (does not contain newlines).
62newtype Line = Line Text
63 deriving (Eq, Ord, Show, Monoid)
64
65#if __GLASGOW_HASKELL__ >= 804
66instance Semigroup Line where
67 (<>) = mappend
68#endif
69
70instance IsString Line where
71 fromString = fromMaybe (throw NewlineForbidden) . textToLine . fromString
72
73-- | Convert a line to a text value.
74lineToText :: Line -> Text
75lineToText (Line t) = t
76
77-- | Split text into lines. The inverse of `linesToText`.
78textToLines :: Text -> NonEmpty Line
79textToLines =
80#if __GLASGOW_HASKELL__ >= 708
81 Data.List.NonEmpty.fromList . coerce (Text.splitOn "\n")
82#else
83 Data.List.NonEmpty.fromList . map unsafeTextToLine . Text.splitOn "\n"
84#endif
85
86-- | Merge lines into a single text value.
87linesToText :: [Line] -> Text
88linesToText =
89#if __GLASGOW_HASKELL__ >= 708
90 coerce Text.unlines
91#else
92 Text.unlines . map lineToText
93#endif
94
95-- | Try to convert a text value into a line.
96-- Precondition (checked): the argument does not contain newlines.
97textToLine :: Text -> Maybe Line
98textToLine = fromSingleton . textToLines
99 where
100 fromSingleton (a :| []) = Just a
101 fromSingleton _ = Nothing
102
103-- | Convert a text value into a line.
104-- Precondition (unchecked): the argument does not contain newlines.
105unsafeTextToLine :: Text -> Line
106unsafeTextToLine = Line