{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-|
Module:      TextShow.Functions
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

Optional orphan 'TextShow', 'TextShow1', and 'TextShow2' instances for functions.

/Since: 2/
-}
module TextShow.Functions () where

import TextShow.Classes (TextShow(..), TextShow1(..), TextShow2(..))

-- | /Since: 2/
instance TextShow (a -> b) where
    showbPrec :: Int -> (a -> b) -> Builder
showbPrec = forall (f :: * -> *) a.
TextShow1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
liftShowbPrec forall a. HasCallStack => a
undefined forall a. HasCallStack => a
undefined
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow1 ((->) a) where
    liftShowbPrec :: forall a.
(Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> (a -> a) -> Builder
liftShowbPrec = forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2 forall a. HasCallStack => a
undefined forall a. HasCallStack => a
undefined
    {-# INLINE liftShowbPrec #-}

-- | /Since: 2/
instance TextShow2 (->) where
    liftShowbPrec2 :: forall a b.
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> (a -> b)
-> Builder
liftShowbPrec2 Int -> a -> Builder
_ [a] -> Builder
_ Int -> b -> Builder
_ [b] -> Builder
_ Int
_ a -> b
_ = Builder
"<function>"
    {-# INLINE liftShowbPrec2 #-}