A cli database for some FFX stuff
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE DeriveTraversable #-}

module Data.NonEmptyList
    ( -- * Types
      NonEmptyList
      -- * Conversions
    , fromList
    , singleton
    , toList
      -- * Manipulation
    , head
    , merge
    , push
    , tail
    , uncons
    ) where

import           Prelude      hiding (head, tail)

import           Data.Aeson

import           GHC.Generics

data NonEmptyList a = NonEmptyList a [a] deriving (Show, Eq, Ord, Functor, Foldable, Traversable, Generic)

singleton :: a -> NonEmptyList a
singleton x = NonEmptyList x []

toList :: NonEmptyList a -> [a]
toList (NonEmptyList h t) = h:t

fromList :: [a] -> Maybe (NonEmptyList a)
fromList []     = Nothing
fromList (x:xs) = Just $ NonEmptyList x xs

push :: a -> NonEmptyList a -> NonEmptyList a
push x (NonEmptyList lx ltail) = NonEmptyList x (lx:ltail)

merge :: NonEmptyList a -> NonEmptyList a -> NonEmptyList a
merge (NonEmptyList a as) (NonEmptyList b bs) = NonEmptyList a $ as ++ [b] ++ bs

head :: NonEmptyList a -> a
head (NonEmptyList x _) = x

tail :: NonEmptyList a -> [a]
tail (NonEmptyList _ x) = x

uncons :: NonEmptyList a -> (a, [a])
uncons (NonEmptyList x xs) = (x, xs)