{- Parts of the Prelude are partial functions, which are a common source of
 - bugs.
 -
 - This exports functions that conflict with the prelude, which avoids
 - them being accidentally used.
 -}

{-# OPTIONS_GHC -fno-warn-tabs #-}

module Utility.PartialPrelude where

import qualified Data.Maybe

{- read should be avoided, as it throws an error
 - Instead, use: readish -}
read :: Read a => String -> a
read :: String -> a
read = String -> a
forall a. Read a => String -> a
Prelude.read

{- head is a partial function; head [] is an error
 - Instead, use: take 1 or headMaybe -}
head :: [a] -> a
head :: [a] -> a
head = [a] -> a
forall a. [a] -> a
Prelude.head

{- tail is also partial
 - Instead, use: drop 1 -}
tail :: [a] -> [a]
tail :: [a] -> [a]
tail = [a] -> [a]
forall a. [a] -> [a]
Prelude.tail

{- init too
 - Instead, use: beginning -}
init :: [a] -> [a]
init :: [a] -> [a]
init = [a] -> [a]
forall a. [a] -> [a]
Prelude.init

{- last too
 - Instead, use: end or lastMaybe -}
last :: [a] -> a
last :: [a] -> a
last = [a] -> a
forall a. [a] -> a
Prelude.last

{- Attempts to read a value from a String.
 -
 - Unlike Text.Read.readMaybe, this ignores some trailing text
 - after the part that can be read. However, if the trailing text looks
 - like another readable value, it fails.
 -}
readish :: Read a => String -> Maybe a
readish :: String -> Maybe a
readish String
s = case ReadS a
forall a. Read a => ReadS a
reads String
s of
	((a
x,String
_):[(a, String)]
_) -> a -> Maybe a
forall a. a -> Maybe a
Just a
x
	[(a, String)]
_ -> Maybe a
forall a. Maybe a
Nothing

{- Like head but Nothing on empty list. -}
headMaybe :: [a] -> Maybe a
headMaybe :: [a] -> Maybe a
headMaybe = [a] -> Maybe a
forall a. [a] -> Maybe a
Data.Maybe.listToMaybe

{- Like last but Nothing on empty list. -}
lastMaybe :: [a] -> Maybe a
lastMaybe :: [a] -> Maybe a
lastMaybe [] = Maybe a
forall a. Maybe a
Nothing
lastMaybe [a]
v = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ [a] -> a
forall a. [a] -> a
Prelude.last [a]
v

{- All but the last element of a list.
 - (Like init, but no error on an empty list.) -}
beginning :: [a] -> [a]
beginning :: [a] -> [a]
beginning [] = []
beginning [a]
l = [a] -> [a]
forall a. [a] -> [a]
Prelude.init [a]
l

{- Like last, but no error on an empty list. -}
end :: [a] -> [a]
end :: [a] -> [a]
end [] = []
end [a]
l = [[a] -> a
forall a. [a] -> a
Prelude.last [a]
l]