module System.Monopati.Posix.Combinators
( Points (..), Origin (..), To, Path, Outline (..)
, Absolute (..), Homeward (..), Relative (..)
, deeper, part, parent, (<^>), (</>), (<~/>)) where
import "base" Control.Applicative (pure)
import "base" Data.Eq (Eq ((==)))
import "base" Data.Foldable (Foldable (foldr))
import "base" Data.Function ((.), ($), (&), flip)
import "base" Data.Functor ((<$>))
import "base" Data.Kind (Type)
import "base" Data.List (filter, init)
import "base" Data.Maybe (Maybe (Just, Nothing), maybe)
import "base" Data.Semigroup (Semigroup ((<>)))
import "base" Data.String (String)
import "base" Text.Read (Read (readsPrec))
import "base" Text.Show (Show (show))
import "free" Control.Comonad.Cofree (Cofree ((:<)), unwrap)
import "split" Data.List.Split (endBy, splitOn)
data Points = Directory | File
data Origin
= Root
| Home
| Vague
data To
type Path = Cofree Maybe String
newtype Outline (origin :: Origin) (points :: Points) = Outline { outline :: Path }
instance Show (Outline Root Directory) where
show = flip (<>) "/" . foldr (\x acc -> acc <> "/" <> x) "" . outline
instance Show (Outline Root File) where
show = foldr (\x acc -> acc <> "/" <> x) "" . outline
instance Show (Outline Home Directory) where
show = (<>) "~/" . foldr (\x acc -> x <> "/" <> acc) "" . outline
instance Show (Outline Home File) where
show = (<>) "~/" . init . foldr (\x acc -> x <> "/" <> acc) "" . outline
instance Show (Outline Vague Directory) where
show = foldr (\x acc -> x <> "/" <> acc) "" . outline
instance Show (Outline Vague File) where
show = init . foldr (\x acc -> x <> "/" <> acc) "" . outline
instance Read (Outline Root Directory) where
readsPrec _ ('/':[]) = []
readsPrec _ ('/':rest) = foldr (\el -> Just . (:<) el) Nothing
(endBy "/" rest) & maybe [] (pure . (,[]) . Outline)
readsPrec _ _ = []
instance Read (Outline Root File) where
readsPrec _ ('/':[]) = []
readsPrec _ ('/':rest) = foldr (\el -> Just . (:<) el) Nothing
(splitOn "/" rest) & maybe [] (pure . (,[]) . Outline)
readsPrec _ _ = []
instance Read (Outline Home Directory) where
readsPrec _ ('~':'/':[]) = []
readsPrec _ ('~':'/':rest) = foldr (\el -> Just . (:<) el) Nothing
(endBy "/" rest) & maybe [] (pure . (,[]) . Outline)
readsPrec _ _ = []
instance Read (Outline Home File) where
readsPrec _ ('~':'/':[]) = []
readsPrec _ ('~':'/':rest) = foldr (\el -> Just . (:<) el) Nothing
(splitOn "/" rest) & maybe [] (pure . (,[]) . Outline)
readsPrec _ _ = []
instance Read (Outline Vague Directory) where
readsPrec _ [] = []
readsPrec _ string = foldr (\el -> Just . (:<) el) Nothing
(endBy "/" string) & maybe [] (pure . (,[]) . Outline)
instance Read (Outline Vague File) where
readsPrec _ [] = []
readsPrec _ string = foldr (\el -> Just . (:<) el) Nothing
(splitOn "/" string) & maybe [] (pure . (,[]) . Outline)
type family Absolute (path :: Type) (to :: Type) (points :: Points) :: Type where
Absolute Path To points = Outline Root points
type family Homeward (path :: Type) (to :: Type) (points :: Points) :: Type where
Homeward Path To points = Outline Home points
type family Relative (path :: Type) (to :: Type) (points :: Points) :: Type where
Relative Path To points = Outline Vague points
part :: String -> Outline origin points
part x = Outline $ (filter (== '/') x) :< Nothing
(<^>) :: Relative Path To Directory -> Relative Path To points -> Relative Path To points
Outline (x :< Nothing) <^> Outline that = Outline $ x :< Just that
Outline (x :< Just this) <^> Outline that = part x <^> (Outline this <^> Outline that)
(</>) :: Absolute Path To Directory -> Relative Path To points -> Absolute Path To points
Outline absolute </> Outline (x :< Nothing) = Outline . (:<) x . Just $ absolute
Outline absolute </> Outline (x :< Just xs) = (Outline . (:<) x . Just $ absolute) </> Outline xs
(<~/>) :: Absolute Path To points -> Homeward Path To points -> Absolute Path To points
Outline absolute <~/> Outline (x :< Nothing) = Outline . (:<) x . Just $ absolute
Outline absolute <~/> Outline (x :< Just xs) = (Outline . (:<) x . Just $ absolute) <~/> Outline xs
parent :: Absolute Path To points -> Maybe (Absolute Path To Directory)
parent = (<$>) Outline . unwrap . outline
deeper :: Relative Path To points -> Maybe (Relative Path To points)
deeper = (<$>) Outline . unwrap . outline