{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeFamilies #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  GHC.IsList
-- Copyright   :  (c) The University of Glasgow 2002
-- License     :  see libraries/base/LICENSE
--
-- Maintainer  :  cvs-ghc@haskell.org
-- Stability   :  internal
-- Portability :  non-portable (GHC Extensions)
--
-- @since 4.17.0.0
-----------------------------------------------------------------------------

module GHC.IsList
  ( IsList(..)
  ) where

import GHC.Base
import GHC.Stack
import Data.Version ( Version(..), makeVersion )
import Control.Applicative (ZipList(..))

-- | The 'IsList' class and its methods are intended to be used in
--   conjunction with the OverloadedLists extension.
--
-- @since 4.7.0.0
class IsList l where
  -- | The 'Item' type function returns the type of items of the structure
  --   @l@.
  type Item l

  -- | The 'fromList' function constructs the structure @l@ from the given
  --   list of @Item l@
  fromList  :: [Item l] -> l

  -- | The 'fromListN' function takes the input list's length and potentially
  --   uses it to construct the structure @l@ more efficiently compared to
  --   'fromList'. If the given number does not equal to the input list's length
  --   the behaviour of 'fromListN' is not specified.
  --
  --   prop> fromListN (length xs) xs == fromList xs
  fromListN :: Int -> [Item l] -> l
  fromListN Int
_ = [Item l] -> l
forall l. IsList l => [Item l] -> l
fromList

  -- | The 'toList' function extracts a list of @Item l@ from the structure @l@.
  --   It should satisfy fromList . toList = id.
  toList :: l -> [Item l]

-- | @since 4.7.0.0
instance IsList [a] where
  type (Item [a]) = a
  fromList :: [Item [a]] -> [a]
fromList = [a] -> [a]
[Item [a]] -> [a]
forall a. a -> a
id
  toList :: [a] -> [Item [a]]
toList = [a] -> [a]
[a] -> [Item [a]]
forall a. a -> a
id

-- | @since 4.15.0.0
instance IsList (ZipList a) where
  type Item (ZipList a) = a
  fromList :: [Item (ZipList a)] -> ZipList a
fromList = [a] -> ZipList a
[Item (ZipList a)] -> ZipList a
forall a. [a] -> ZipList a
ZipList
  toList :: ZipList a -> [Item (ZipList a)]
toList = ZipList a -> [a]
ZipList a -> [Item (ZipList a)]
forall a. ZipList a -> [a]
getZipList

-- | @since 4.9.0.0
instance IsList (NonEmpty a) where
  type Item (NonEmpty a) = a

  fromList :: [Item (NonEmpty a)] -> NonEmpty a
fromList (Item (NonEmpty a)
a:[Item (NonEmpty a)]
as) = a
Item (NonEmpty a)
a a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
[Item (NonEmpty a)]
as
  fromList [] = [Char] -> NonEmpty a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NonEmpty.fromList: empty list"

  toList :: NonEmpty a -> [Item (NonEmpty a)]
toList ~(a
a :| [a]
as) = a
a a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
as

-- | @since 4.8.0.0
instance IsList Version where
  type (Item Version) = Int
  fromList :: [Item Version] -> Version
fromList = [Int] -> Version
[Item Version] -> Version
makeVersion
  toList :: Version -> [Item Version]
toList = Version -> [Int]
Version -> [Item Version]
versionBranch

-- | Be aware that 'fromList . toList = id' only for unfrozen 'CallStack's,
-- since 'toList' removes frozenness information.
--
-- @since 4.9.0.0
instance IsList CallStack where
  type (Item CallStack) = (String, SrcLoc)
  fromList :: [Item CallStack] -> CallStack
fromList = [([Char], SrcLoc)] -> CallStack
[Item CallStack] -> CallStack
fromCallSiteList
  toList :: CallStack -> [Item CallStack]
toList   = CallStack -> [([Char], SrcLoc)]
CallStack -> [Item CallStack]
getCallStack