{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | Commonly useful functions, a Prelude replacement.
--
-- This is designed to be imported everywhere, unqualified (generally
-- the only unqualified import you should use).
--
-- Alpha can be opinionated and break with other Haskell idioms. For
-- example, we define our own operators which have a pattern to their
-- characters:
--
-- - `|` normal function-level applications
-- - `/` indicates doing something inside a functor
-- - `<` and `>` indicate the direction in which values flow
--   between functions
--
-- It seems unnecessarily different at first but it makes things easier
-- to read quickly.
module Alpha
  ( -- * Re-export Protolude
    module X,
    String,

    -- * Composing
    compose,
    (.>),
    (<.),

    -- * Applying
    (<|),
    (|>),

    -- * Mapping
    (/>),
    (</),
    (<//),

    -- * Bool
    don't,

    -- * Text
    chomp,
    lchomp,
    joinWith,
    CanSnakeCase (snake),
    wrap,

    -- * String
    capitalize,
    lowercase,

    -- * Data Validation
    require,

    -- * Debugging tools
    say,
  )
where

import qualified Data.Char as Char
import qualified Data.List as List
import Data.String
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LazyText
import Protolude as X hiding (($), (&), (.))

-- | Debugging printf
say :: Text -> IO ()
say = putText

-- | Composition
compose :: (a -> b) -> (b -> c) -> (a -> c)
compose f g x = g (f x)

-- | Right-composition operator
infixl 9 .>

(.>) :: (a -> b) -> (b -> c) -> (a -> c)
f .> g = compose f g

-- | Left-composition operator
infixr 9 <.

(<.) :: (b -> c) -> (a -> b) -> (a -> c)
g <. f = compose f g

-- | Alias for map, fmap, <$>
(</) :: Functor f => (a -> b) -> f a -> f b
f </ g = fmap f g

-- | Double fmap. A function on the left goes "into" two functors
-- (i.e. it goes "two levels deep"), applies the function to the inner
-- values, then returns the result wrapped in the two functors.
(<//) :: (Functor f0, Functor f1) => (a -> b) -> f0 (f1 a) -> f0 (f1 b)
(<//) = fmap .> fmap

-- | Normal function application. Do the right side, then pass the
-- return value to the function on the left side.
infixr 0 <|

(<|) :: (a -> b) -> a -> b
f <| g = f g

-- | Reverse function application. Do the left side, then pass the
-- return value to the function on the right side.
infixl 0 |>

(|>) :: a -> (a -> b) -> b
f |> g = g f

-- | Alias for <&>. Can be read as "and then". Basically does into a
-- functor, does some computation, then returns the same kind of
-- functor. Could also be defined as `f >>= return <. g`
(/>) :: Functor f => f a -> (a -> b) -> f b
f /> g = fmap g f

-- | Removes newlines from text.
chomp :: Text -> Text
chomp = Text.filter (/= '\n')

-- | Removes newlines from lazy text.
lchomp :: LazyText.Text -> LazyText.Text
lchomp = LazyText.filter (/= '\n')

-- | Join a list of things with a separator.
joinWith :: [a] -> [[a]] -> [a]
joinWith = intercalate

-- | can you just not
don't :: Bool -> Bool
don't = do not
{-# ANN don't ("HLint: ignore Redundant do" :: String) #-}

-- | Class for turning different string types to snakeCase.
class CanSnakeCase str where
  snake :: str -> str

instance CanSnakeCase Text where
  snake = Text.toLower .> Text.replace " " "-"

capitalize :: String -> String
capitalize [] = []
capitalize str = (Char.toUpper <| List.head str) : (Char.toLower </ List.tail str)

lowercase :: String -> String
lowercase str = [Char.toLower c | c <- str]

require :: Text -> Maybe a -> a
require _ (Just x) = x
require s Nothing = panic <| s <> " not found"

-- | Wrap text at the given limit.
wrap :: Int -> Text -> Text
wrap lim = Text.words .> wrap_ 0 .> Text.unwords
  where
    wrap_ :: Int -> [Text] -> [Text]
    wrap_ _ [] = []
    wrap_ pos (w : ws)
      | pos == 0 = w : wrap_ (pos + lw) ws
      | pos + lw + 1 > lim = wrap_ 0 (Text.cons '\n' w : ws)
      | otherwise = w : wrap_ (pos + lw + 1) ws
      where
        lw = Text.length w