Skip to content

Instantly share code, notes, and snippets.

@hasufell
Last active January 19, 2020 18:24
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save hasufell/27dc83c979f4a0e996015972c388826a to your computer and use it in GitHub Desktop.
Save hasufell/27dc83c979f4a0e996015972c388826a to your computer and use it in GitHub Desktop.
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeInType #-}
module MyPath where
import Data.Maybe
import Data.Typeable
import GHC.TypeLits (ErrorMessage(..), TypeError)
import System.Directory
parseAbs :: FilePath -> Maybe (Path Abs)
parseAbs = pure . Path -- simplified
parseRel :: FilePath -> Maybe (Path Rel)
parseRel = pure . Path
parseFn :: FilePath -> Maybe (Path Fn)
parseFn = pure . Path
data Path (a :: PathType) = Path FilePath
deriving (Show, Eq, Ord, Typeable)
data PathType = Abs
| Rel
| Fn
| Any
type family UpCast (from :: PathType) :: PathType where
UpCast 'Abs = 'Abs
UpCast 'Rel = 'Rel
UpCast 'Fn = 'Rel
UpCast 'Any = TypeError ('Text "Any cannot be upcasted")
(</>) :: (UpCast r ~ 'Rel) => Path b -> Path r -> Path (UpCast b)
(</>) (Path a) (Path b) = Path (a ++ "/" ++ b) -- simplified
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment