-- |
-- Module:     System.Directory.OsPath.Types
-- Copyright:  (c) Sergey Vinokurov 2024
-- License:    Apache-2.0 (see LICENSE)
-- Maintainer: serg.foo@gmail.com

{-# LANGUAGE DeriveFoldable             #-}
{-# LANGUAGE DeriveFunctor              #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE DeriveTraversable          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module System.Directory.OsPath.Types
  ( SymlinkType(..)
  , FileType(..)
  , Basename(..)
  , Relative(..)
  ) where

import Control.DeepSeq (NFData)
import GHC.Generics (Generic, Generic1)

data SymlinkType = Regular | Symlink
  deriving (Int -> SymlinkType -> ShowS
[SymlinkType] -> ShowS
SymlinkType -> String
(Int -> SymlinkType -> ShowS)
-> (SymlinkType -> String)
-> ([SymlinkType] -> ShowS)
-> Show SymlinkType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SymlinkType -> ShowS
showsPrec :: Int -> SymlinkType -> ShowS
$cshow :: SymlinkType -> String
show :: SymlinkType -> String
$cshowList :: [SymlinkType] -> ShowS
showList :: [SymlinkType] -> ShowS
Show, ReadPrec [SymlinkType]
ReadPrec SymlinkType
Int -> ReadS SymlinkType
ReadS [SymlinkType]
(Int -> ReadS SymlinkType)
-> ReadS [SymlinkType]
-> ReadPrec SymlinkType
-> ReadPrec [SymlinkType]
-> Read SymlinkType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SymlinkType
readsPrec :: Int -> ReadS SymlinkType
$creadList :: ReadS [SymlinkType]
readList :: ReadS [SymlinkType]
$creadPrec :: ReadPrec SymlinkType
readPrec :: ReadPrec SymlinkType
$creadListPrec :: ReadPrec [SymlinkType]
readListPrec :: ReadPrec [SymlinkType]
Read, SymlinkType -> SymlinkType -> Bool
(SymlinkType -> SymlinkType -> Bool)
-> (SymlinkType -> SymlinkType -> Bool) -> Eq SymlinkType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SymlinkType -> SymlinkType -> Bool
== :: SymlinkType -> SymlinkType -> Bool
$c/= :: SymlinkType -> SymlinkType -> Bool
/= :: SymlinkType -> SymlinkType -> Bool
Eq, Eq SymlinkType
Eq SymlinkType =>
(SymlinkType -> SymlinkType -> Ordering)
-> (SymlinkType -> SymlinkType -> Bool)
-> (SymlinkType -> SymlinkType -> Bool)
-> (SymlinkType -> SymlinkType -> Bool)
-> (SymlinkType -> SymlinkType -> Bool)
-> (SymlinkType -> SymlinkType -> SymlinkType)
-> (SymlinkType -> SymlinkType -> SymlinkType)
-> Ord SymlinkType
SymlinkType -> SymlinkType -> Bool
SymlinkType -> SymlinkType -> Ordering
SymlinkType -> SymlinkType -> SymlinkType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SymlinkType -> SymlinkType -> Ordering
compare :: SymlinkType -> SymlinkType -> Ordering
$c< :: SymlinkType -> SymlinkType -> Bool
< :: SymlinkType -> SymlinkType -> Bool
$c<= :: SymlinkType -> SymlinkType -> Bool
<= :: SymlinkType -> SymlinkType -> Bool
$c> :: SymlinkType -> SymlinkType -> Bool
> :: SymlinkType -> SymlinkType -> Bool
$c>= :: SymlinkType -> SymlinkType -> Bool
>= :: SymlinkType -> SymlinkType -> Bool
$cmax :: SymlinkType -> SymlinkType -> SymlinkType
max :: SymlinkType -> SymlinkType -> SymlinkType
$cmin :: SymlinkType -> SymlinkType -> SymlinkType
min :: SymlinkType -> SymlinkType -> SymlinkType
Ord, (forall x. SymlinkType -> Rep SymlinkType x)
-> (forall x. Rep SymlinkType x -> SymlinkType)
-> Generic SymlinkType
forall x. Rep SymlinkType x -> SymlinkType
forall x. SymlinkType -> Rep SymlinkType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SymlinkType -> Rep SymlinkType x
from :: forall x. SymlinkType -> Rep SymlinkType x
$cto :: forall x. Rep SymlinkType x -> SymlinkType
to :: forall x. Rep SymlinkType x -> SymlinkType
Generic)

instance NFData SymlinkType

data FileType
  = File {-# UNPACK #-} !SymlinkType
  | Directory {-# UNPACK #-} !SymlinkType
  | Other {-# UNPACK #-} !SymlinkType
  deriving (Int -> FileType -> ShowS
[FileType] -> ShowS
FileType -> String
(Int -> FileType -> ShowS)
-> (FileType -> String) -> ([FileType] -> ShowS) -> Show FileType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileType -> ShowS
showsPrec :: Int -> FileType -> ShowS
$cshow :: FileType -> String
show :: FileType -> String
$cshowList :: [FileType] -> ShowS
showList :: [FileType] -> ShowS
Show, ReadPrec [FileType]
ReadPrec FileType
Int -> ReadS FileType
ReadS [FileType]
(Int -> ReadS FileType)
-> ReadS [FileType]
-> ReadPrec FileType
-> ReadPrec [FileType]
-> Read FileType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FileType
readsPrec :: Int -> ReadS FileType
$creadList :: ReadS [FileType]
readList :: ReadS [FileType]
$creadPrec :: ReadPrec FileType
readPrec :: ReadPrec FileType
$creadListPrec :: ReadPrec [FileType]
readListPrec :: ReadPrec [FileType]
Read, FileType -> FileType -> Bool
(FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool) -> Eq FileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileType -> FileType -> Bool
== :: FileType -> FileType -> Bool
$c/= :: FileType -> FileType -> Bool
/= :: FileType -> FileType -> Bool
Eq, Eq FileType
Eq FileType =>
(FileType -> FileType -> Ordering)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> FileType)
-> (FileType -> FileType -> FileType)
-> Ord FileType
FileType -> FileType -> Bool
FileType -> FileType -> Ordering
FileType -> FileType -> FileType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileType -> FileType -> Ordering
compare :: FileType -> FileType -> Ordering
$c< :: FileType -> FileType -> Bool
< :: FileType -> FileType -> Bool
$c<= :: FileType -> FileType -> Bool
<= :: FileType -> FileType -> Bool
$c> :: FileType -> FileType -> Bool
> :: FileType -> FileType -> Bool
$c>= :: FileType -> FileType -> Bool
>= :: FileType -> FileType -> Bool
$cmax :: FileType -> FileType -> FileType
max :: FileType -> FileType -> FileType
$cmin :: FileType -> FileType -> FileType
min :: FileType -> FileType -> FileType
Ord, (forall x. FileType -> Rep FileType x)
-> (forall x. Rep FileType x -> FileType) -> Generic FileType
forall x. Rep FileType x -> FileType
forall x. FileType -> Rep FileType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FileType -> Rep FileType x
from :: forall x. FileType -> Rep FileType x
$cto :: forall x. Rep FileType x -> FileType
to :: forall x. Rep FileType x -> FileType
Generic)

instance NFData FileType

-- | Basename part of filename, without directory separators.
newtype Basename a = Basename { forall a. Basename a -> a
unBasename :: a }
  deriving (Basename a -> Basename a -> Bool
(Basename a -> Basename a -> Bool)
-> (Basename a -> Basename a -> Bool) -> Eq (Basename a)
forall a. Eq a => Basename a -> Basename a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Basename a -> Basename a -> Bool
== :: Basename a -> Basename a -> Bool
$c/= :: forall a. Eq a => Basename a -> Basename a -> Bool
/= :: Basename a -> Basename a -> Bool
Eq, Eq (Basename a)
Eq (Basename a) =>
(Basename a -> Basename a -> Ordering)
-> (Basename a -> Basename a -> Bool)
-> (Basename a -> Basename a -> Bool)
-> (Basename a -> Basename a -> Bool)
-> (Basename a -> Basename a -> Bool)
-> (Basename a -> Basename a -> Basename a)
-> (Basename a -> Basename a -> Basename a)
-> Ord (Basename a)
Basename a -> Basename a -> Bool
Basename a -> Basename a -> Ordering
Basename a -> Basename a -> Basename a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Basename a)
forall a. Ord a => Basename a -> Basename a -> Bool
forall a. Ord a => Basename a -> Basename a -> Ordering
forall a. Ord a => Basename a -> Basename a -> Basename a
$ccompare :: forall a. Ord a => Basename a -> Basename a -> Ordering
compare :: Basename a -> Basename a -> Ordering
$c< :: forall a. Ord a => Basename a -> Basename a -> Bool
< :: Basename a -> Basename a -> Bool
$c<= :: forall a. Ord a => Basename a -> Basename a -> Bool
<= :: Basename a -> Basename a -> Bool
$c> :: forall a. Ord a => Basename a -> Basename a -> Bool
> :: Basename a -> Basename a -> Bool
$c>= :: forall a. Ord a => Basename a -> Basename a -> Bool
>= :: Basename a -> Basename a -> Bool
$cmax :: forall a. Ord a => Basename a -> Basename a -> Basename a
max :: Basename a -> Basename a -> Basename a
$cmin :: forall a. Ord a => Basename a -> Basename a -> Basename a
min :: Basename a -> Basename a -> Basename a
Ord, Int -> Basename a -> ShowS
[Basename a] -> ShowS
Basename a -> String
(Int -> Basename a -> ShowS)
-> (Basename a -> String)
-> ([Basename a] -> ShowS)
-> Show (Basename a)
forall a. Show a => Int -> Basename a -> ShowS
forall a. Show a => [Basename a] -> ShowS
forall a. Show a => Basename a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Basename a -> ShowS
showsPrec :: Int -> Basename a -> ShowS
$cshow :: forall a. Show a => Basename a -> String
show :: Basename a -> String
$cshowList :: forall a. Show a => [Basename a] -> ShowS
showList :: [Basename a] -> ShowS
Show, (forall x. Basename a -> Rep (Basename a) x)
-> (forall x. Rep (Basename a) x -> Basename a)
-> Generic (Basename a)
forall x. Rep (Basename a) x -> Basename a
forall x. Basename a -> Rep (Basename a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Basename a) x -> Basename a
forall a x. Basename a -> Rep (Basename a) x
$cfrom :: forall a x. Basename a -> Rep (Basename a) x
from :: forall x. Basename a -> Rep (Basename a) x
$cto :: forall a x. Rep (Basename a) x -> Basename a
to :: forall x. Rep (Basename a) x -> Basename a
Generic, (forall a. Basename a -> Rep1 Basename a)
-> (forall a. Rep1 Basename a -> Basename a) -> Generic1 Basename
forall a. Rep1 Basename a -> Basename a
forall a. Basename a -> Rep1 Basename a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. Basename a -> Rep1 Basename a
from1 :: forall a. Basename a -> Rep1 Basename a
$cto1 :: forall a. Rep1 Basename a -> Basename a
to1 :: forall a. Rep1 Basename a -> Basename a
Generic1, Basename a -> ()
(Basename a -> ()) -> NFData (Basename a)
forall a. NFData a => Basename a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => Basename a -> ()
rnf :: Basename a -> ()
NFData, (forall a b. (a -> b) -> Basename a -> Basename b)
-> (forall a b. a -> Basename b -> Basename a) -> Functor Basename
forall a b. a -> Basename b -> Basename a
forall a b. (a -> b) -> Basename a -> Basename b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Basename a -> Basename b
fmap :: forall a b. (a -> b) -> Basename a -> Basename b
$c<$ :: forall a b. a -> Basename b -> Basename a
<$ :: forall a b. a -> Basename b -> Basename a
Functor, (forall m. Monoid m => Basename m -> m)
-> (forall m a. Monoid m => (a -> m) -> Basename a -> m)
-> (forall m a. Monoid m => (a -> m) -> Basename a -> m)
-> (forall a b. (a -> b -> b) -> b -> Basename a -> b)
-> (forall a b. (a -> b -> b) -> b -> Basename a -> b)
-> (forall b a. (b -> a -> b) -> b -> Basename a -> b)
-> (forall b a. (b -> a -> b) -> b -> Basename a -> b)
-> (forall a. (a -> a -> a) -> Basename a -> a)
-> (forall a. (a -> a -> a) -> Basename a -> a)
-> (forall a. Basename a -> [a])
-> (forall a. Basename a -> Bool)
-> (forall a. Basename a -> Int)
-> (forall a. Eq a => a -> Basename a -> Bool)
-> (forall a. Ord a => Basename a -> a)
-> (forall a. Ord a => Basename a -> a)
-> (forall a. Num a => Basename a -> a)
-> (forall a. Num a => Basename a -> a)
-> Foldable Basename
forall a. Eq a => a -> Basename a -> Bool
forall a. Num a => Basename a -> a
forall a. Ord a => Basename a -> a
forall m. Monoid m => Basename m -> m
forall a. Basename a -> Bool
forall a. Basename a -> Int
forall a. Basename a -> [a]
forall a. (a -> a -> a) -> Basename a -> a
forall m a. Monoid m => (a -> m) -> Basename a -> m
forall b a. (b -> a -> b) -> b -> Basename a -> b
forall a b. (a -> b -> b) -> b -> Basename a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => Basename m -> m
fold :: forall m. Monoid m => Basename m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Basename a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Basename a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Basename a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Basename a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Basename a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Basename a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Basename a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Basename a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Basename a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Basename a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Basename a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Basename a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Basename a -> a
foldr1 :: forall a. (a -> a -> a) -> Basename a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Basename a -> a
foldl1 :: forall a. (a -> a -> a) -> Basename a -> a
$ctoList :: forall a. Basename a -> [a]
toList :: forall a. Basename a -> [a]
$cnull :: forall a. Basename a -> Bool
null :: forall a. Basename a -> Bool
$clength :: forall a. Basename a -> Int
length :: forall a. Basename a -> Int
$celem :: forall a. Eq a => a -> Basename a -> Bool
elem :: forall a. Eq a => a -> Basename a -> Bool
$cmaximum :: forall a. Ord a => Basename a -> a
maximum :: forall a. Ord a => Basename a -> a
$cminimum :: forall a. Ord a => Basename a -> a
minimum :: forall a. Ord a => Basename a -> a
$csum :: forall a. Num a => Basename a -> a
sum :: forall a. Num a => Basename a -> a
$cproduct :: forall a. Num a => Basename a -> a
product :: forall a. Num a => Basename a -> a
Foldable, Functor Basename
Foldable Basename
(Functor Basename, Foldable Basename) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Basename a -> f (Basename b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Basename (f a) -> f (Basename a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Basename a -> m (Basename b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Basename (m a) -> m (Basename a))
-> Traversable Basename
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Basename (m a) -> m (Basename a)
forall (f :: * -> *) a.
Applicative f =>
Basename (f a) -> f (Basename a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Basename a -> m (Basename b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Basename a -> f (Basename b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Basename a -> f (Basename b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Basename a -> f (Basename b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Basename (f a) -> f (Basename a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Basename (f a) -> f (Basename a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Basename a -> m (Basename b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Basename a -> m (Basename b)
$csequence :: forall (m :: * -> *) a. Monad m => Basename (m a) -> m (Basename a)
sequence :: forall (m :: * -> *) a. Monad m => Basename (m a) -> m (Basename a)
Traversable)

-- | Filename relative to some other path.
newtype Relative a = Relative { forall a. Relative a -> a
unRelative :: a }
  deriving (Relative a -> Relative a -> Bool
(Relative a -> Relative a -> Bool)
-> (Relative a -> Relative a -> Bool) -> Eq (Relative a)
forall a. Eq a => Relative a -> Relative a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Relative a -> Relative a -> Bool
== :: Relative a -> Relative a -> Bool
$c/= :: forall a. Eq a => Relative a -> Relative a -> Bool
/= :: Relative a -> Relative a -> Bool
Eq, Eq (Relative a)
Eq (Relative a) =>
(Relative a -> Relative a -> Ordering)
-> (Relative a -> Relative a -> Bool)
-> (Relative a -> Relative a -> Bool)
-> (Relative a -> Relative a -> Bool)
-> (Relative a -> Relative a -> Bool)
-> (Relative a -> Relative a -> Relative a)
-> (Relative a -> Relative a -> Relative a)
-> Ord (Relative a)
Relative a -> Relative a -> Bool
Relative a -> Relative a -> Ordering
Relative a -> Relative a -> Relative a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Relative a)
forall a. Ord a => Relative a -> Relative a -> Bool
forall a. Ord a => Relative a -> Relative a -> Ordering
forall a. Ord a => Relative a -> Relative a -> Relative a
$ccompare :: forall a. Ord a => Relative a -> Relative a -> Ordering
compare :: Relative a -> Relative a -> Ordering
$c< :: forall a. Ord a => Relative a -> Relative a -> Bool
< :: Relative a -> Relative a -> Bool
$c<= :: forall a. Ord a => Relative a -> Relative a -> Bool
<= :: Relative a -> Relative a -> Bool
$c> :: forall a. Ord a => Relative a -> Relative a -> Bool
> :: Relative a -> Relative a -> Bool
$c>= :: forall a. Ord a => Relative a -> Relative a -> Bool
>= :: Relative a -> Relative a -> Bool
$cmax :: forall a. Ord a => Relative a -> Relative a -> Relative a
max :: Relative a -> Relative a -> Relative a
$cmin :: forall a. Ord a => Relative a -> Relative a -> Relative a
min :: Relative a -> Relative a -> Relative a
Ord, Int -> Relative a -> ShowS
[Relative a] -> ShowS
Relative a -> String
(Int -> Relative a -> ShowS)
-> (Relative a -> String)
-> ([Relative a] -> ShowS)
-> Show (Relative a)
forall a. Show a => Int -> Relative a -> ShowS
forall a. Show a => [Relative a] -> ShowS
forall a. Show a => Relative a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Relative a -> ShowS
showsPrec :: Int -> Relative a -> ShowS
$cshow :: forall a. Show a => Relative a -> String
show :: Relative a -> String
$cshowList :: forall a. Show a => [Relative a] -> ShowS
showList :: [Relative a] -> ShowS
Show, (forall x. Relative a -> Rep (Relative a) x)
-> (forall x. Rep (Relative a) x -> Relative a)
-> Generic (Relative a)
forall x. Rep (Relative a) x -> Relative a
forall x. Relative a -> Rep (Relative a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Relative a) x -> Relative a
forall a x. Relative a -> Rep (Relative a) x
$cfrom :: forall a x. Relative a -> Rep (Relative a) x
from :: forall x. Relative a -> Rep (Relative a) x
$cto :: forall a x. Rep (Relative a) x -> Relative a
to :: forall x. Rep (Relative a) x -> Relative a
Generic, (forall a. Relative a -> Rep1 Relative a)
-> (forall a. Rep1 Relative a -> Relative a) -> Generic1 Relative
forall a. Rep1 Relative a -> Relative a
forall a. Relative a -> Rep1 Relative a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. Relative a -> Rep1 Relative a
from1 :: forall a. Relative a -> Rep1 Relative a
$cto1 :: forall a. Rep1 Relative a -> Relative a
to1 :: forall a. Rep1 Relative a -> Relative a
Generic1, Relative a -> ()
(Relative a -> ()) -> NFData (Relative a)
forall a. NFData a => Relative a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => Relative a -> ()
rnf :: Relative a -> ()
NFData, (forall a b. (a -> b) -> Relative a -> Relative b)
-> (forall a b. a -> Relative b -> Relative a) -> Functor Relative
forall a b. a -> Relative b -> Relative a
forall a b. (a -> b) -> Relative a -> Relative b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Relative a -> Relative b
fmap :: forall a b. (a -> b) -> Relative a -> Relative b
$c<$ :: forall a b. a -> Relative b -> Relative a
<$ :: forall a b. a -> Relative b -> Relative a
Functor, (forall m. Monoid m => Relative m -> m)
-> (forall m a. Monoid m => (a -> m) -> Relative a -> m)
-> (forall m a. Monoid m => (a -> m) -> Relative a -> m)
-> (forall a b. (a -> b -> b) -> b -> Relative a -> b)
-> (forall a b. (a -> b -> b) -> b -> Relative a -> b)
-> (forall b a. (b -> a -> b) -> b -> Relative a -> b)
-> (forall b a. (b -> a -> b) -> b -> Relative a -> b)
-> (forall a. (a -> a -> a) -> Relative a -> a)
-> (forall a. (a -> a -> a) -> Relative a -> a)
-> (forall a. Relative a -> [a])
-> (forall a. Relative a -> Bool)
-> (forall a. Relative a -> Int)
-> (forall a. Eq a => a -> Relative a -> Bool)
-> (forall a. Ord a => Relative a -> a)
-> (forall a. Ord a => Relative a -> a)
-> (forall a. Num a => Relative a -> a)
-> (forall a. Num a => Relative a -> a)
-> Foldable Relative
forall a. Eq a => a -> Relative a -> Bool
forall a. Num a => Relative a -> a
forall a. Ord a => Relative a -> a
forall m. Monoid m => Relative m -> m
forall a. Relative a -> Bool
forall a. Relative a -> Int
forall a. Relative a -> [a]
forall a. (a -> a -> a) -> Relative a -> a
forall m a. Monoid m => (a -> m) -> Relative a -> m
forall b a. (b -> a -> b) -> b -> Relative a -> b
forall a b. (a -> b -> b) -> b -> Relative a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => Relative m -> m
fold :: forall m. Monoid m => Relative m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Relative a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Relative a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Relative a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Relative a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Relative a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Relative a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Relative a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Relative a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Relative a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Relative a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Relative a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Relative a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Relative a -> a
foldr1 :: forall a. (a -> a -> a) -> Relative a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Relative a -> a
foldl1 :: forall a. (a -> a -> a) -> Relative a -> a
$ctoList :: forall a. Relative a -> [a]
toList :: forall a. Relative a -> [a]
$cnull :: forall a. Relative a -> Bool
null :: forall a. Relative a -> Bool
$clength :: forall a. Relative a -> Int
length :: forall a. Relative a -> Int
$celem :: forall a. Eq a => a -> Relative a -> Bool
elem :: forall a. Eq a => a -> Relative a -> Bool
$cmaximum :: forall a. Ord a => Relative a -> a
maximum :: forall a. Ord a => Relative a -> a
$cminimum :: forall a. Ord a => Relative a -> a
minimum :: forall a. Ord a => Relative a -> a
$csum :: forall a. Num a => Relative a -> a
sum :: forall a. Num a => Relative a -> a
$cproduct :: forall a. Num a => Relative a -> a
product :: forall a. Num a => Relative a -> a
Foldable, Functor Relative
Foldable Relative
(Functor Relative, Foldable Relative) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Relative a -> f (Relative b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Relative (f a) -> f (Relative a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Relative a -> m (Relative b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Relative (m a) -> m (Relative a))
-> Traversable Relative
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Relative (m a) -> m (Relative a)
forall (f :: * -> *) a.
Applicative f =>
Relative (f a) -> f (Relative a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Relative a -> m (Relative b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Relative a -> f (Relative b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Relative a -> f (Relative b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Relative a -> f (Relative b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Relative (f a) -> f (Relative a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Relative (f a) -> f (Relative a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Relative a -> m (Relative b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Relative a -> m (Relative b)
$csequence :: forall (m :: * -> *) a. Monad m => Relative (m a) -> m (Relative a)
sequence :: forall (m :: * -> *) a. Monad m => Relative (m a) -> m (Relative a)
Traversable)