{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}

-- | This module exists primarily for symmetry with "Data.List.Snoc"
-- However, it can also be used in place of the "Prelude" list type:
--
-- This module only exports functions that are efficient on linked lists. Many
-- functions on that type ('Prelude.last' 'Data.List.isSuffixOf') though
-- technically implementable, do not represent the intended use of a linked list
-- in terms of performance.
--
-- Additionally, this module does not export any partial functions: 'head' and
-- 'tail' return their results under a 'Maybe'.
module Data.List.Cons
  ( List
  , pattern Nil
  , pattern Cons
  , nil
  , cons
  , uncons
  , singleton
  , head
  , tail
  ) where

import Prelude hiding (head,tail)

-- | As a counterpart to 'Data.List.Snoc.RList'/'Data.List.Snoc.Tsil'.
type List = ([])

{-# COMPLETE Nil, Cons #-}

-- | An empty 'List', such as 'nil'.
pattern Nil :: List a
pattern $bNil :: List a
$mNil :: forall r a. List a -> (Void# -> r) -> (Void# -> r) -> r
Nil = []

-- | The 'List' consisting of head and tail elements, such as created by 'cons'.
pattern Cons :: a -> List a -> List a
pattern $bCons :: a -> List a -> List a
$mCons :: forall r a. List a -> (a -> List a -> r) -> (Void# -> r) -> r
Cons x xs <- (uncons -> Just (x, xs))
  where Cons = a -> List a -> List a
forall a. a -> List a -> List a
cons

-- | The empty 'List'.
nil :: List a
{-# INLINABLE nil #-}
nil :: List a
nil = []

-- | @O(1)@ Append an element.
--
-- If you are looking for @snoc@, you should use an 'RList', or a finite sequence/queue type.
cons :: a -> List a -> List a
{-# INLINABLE cons #-}
cons :: a -> List a -> List a
cons = (:)

-- | @O(1)@ Access the first element and trailing portion of the list.
-- See also 'head' and 'tail' if you only need one component.
--
-- If you are looking for @unsnoc@, you should use an 'RList', or a finite sequence/queue type.
uncons :: List a -> Maybe (a, List a)
{-# INLINABLE uncons #-}
uncons :: List a -> Maybe (a, List a)
uncons [] = Maybe (a, List a)
forall a. Maybe a
Nothing
uncons (a
x:List a
xs) = (a, List a) -> Maybe (a, List a)
forall a. a -> Maybe a
Just (a
x, List a
xs)

-- | @O(1)@ extract the first element of a list, if it exists.
-- See also 'uncons' if you also need 'tail' at the same time.
head :: List a -> Maybe a
head :: List a -> Maybe a
head List a
Nil = Maybe a
forall a. Maybe a
Nothing
head (Cons a
x List a
_) = a -> Maybe a
forall a. a -> Maybe a
Just a
x

-- | @O(1)@ extract the elements of a list other than the last, if they exist.
-- See also 'uncons' if you also need 'head' at the same time.
tail :: List a -> Maybe (List a)
tail :: List a -> Maybe (List a)
tail List a
Nil = Maybe (List a)
forall a. Maybe a
Nothing
tail (Cons a
_ List a
xs) = List a -> Maybe (List a)
forall a. a -> Maybe a
Just List a
xs

-- | Create a single-element 'List'.
singleton :: a -> List a
{-# INLINE singleton #-}
singleton :: a -> List a
singleton = (a -> List a -> List a
forall a. a -> List a -> List a
:[])