{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Text.LambdaOptions.Parseable (
Parseable(..),
maybeParse,
boundedParse,
repeatedParse,
simpleParse,
) where
import Data.Proxy
( Proxy(..)
)
import GHC.TypeLits
( KnownNat, SomeNat, natVal, someNatVal
, KnownSymbol, SomeSymbol, symbolVal, someSymbolVal
)
import Text.Read
( readMaybe
)
import Text.Read.Bounded
( BoundedRead(..), ReadBounded(..)
)
class Parseable a where
parse :: [String] -> (Maybe a, Int)
maybeParse :: (String -> Maybe a) -> ([String] -> (Maybe a, Int))
maybeParse parser = \case
[] -> (Nothing, 0)
s : _ -> case parser s of
Nothing -> (Nothing, 0)
Just x -> (Just x, 1)
{-# DEPRECATED simpleParse "Use 'maybeParse' instead." #-}
simpleParse :: (String -> Maybe a) -> ([String] -> (Maybe a, Int))
simpleParse = maybeParse
boundedParse :: (String -> BoundedRead a) -> ([String] -> (Maybe a, Int))
boundedParse parser = maybeParse $ \s -> case parser s of
NoRead -> Nothing
ClampedRead _ -> Nothing
ExactRead x -> Just x
repeatedParse :: (Parseable a) => Int -> [String] -> (Maybe [a], Int)
repeatedParse n = toPair . repeatedParse' n
repeatedParse' :: (Parseable a) => Int -> [String] -> (Maybe [a], Int, [String])
repeatedParse' n ss = case n <= 0 of
True -> (Just [], 0, ss)
False -> let
(mx, nx) = parse ss
sx = drop nx ss
in case mx of
Nothing -> (Nothing, nx, sx)
Just x -> let
(mxs, nxs, sxs) = repeatedParse' (n - 1) sx
in (fmap (x :) mxs, nx + nxs, sxs)
instance Parseable Word where
parse = boundedParse readBounded
instance Parseable Int where
parse = boundedParse readBounded
instance Parseable Integer where
parse = maybeParse readMaybe
instance Parseable Char where
parse strs = case strs of
[c] : _ -> (Just c, 1)
_ -> (Nothing, 0)
instance Parseable String where
parse = maybeParse Just
instance Parseable Float where
parse = maybeParse readMaybe
instance Parseable Double where
parse = maybeParse readMaybe
instance (Parseable a) => Parseable (Maybe a) where
parse args = case parse args of
(Nothing, n) -> (Just Nothing, n)
(Just x, n) -> (Just $ Just x, n)
instance (KnownNat n) => Parseable (Proxy n) where
parse = \case
[] -> (Nothing, 0)
str : _ -> case show (natVal nat) == str of
True -> (Just nat, 1)
False -> (Nothing, 0)
where
nat = Proxy :: Proxy n
instance (KnownSymbol s) => Parseable (Proxy s) where
parse = \case
[] -> (Nothing, 0)
str : _ -> case symbolVal sym == str of
True -> (Just sym, 1)
False -> (Nothing, 0)
where
sym = Proxy :: Proxy s
instance Parseable SomeSymbol where
parse = \case
[] -> (Nothing, 0)
str : _ -> (Just $ someSymbolVal str, 1)
instance Parseable SomeNat where
parse = \case
[] -> (Nothing, 0)
s : _ -> case readMaybe s of
Nothing -> (Nothing, 0)
Just n -> case show n == s of
False -> (Nothing, 0)
True -> case someNatVal n of
Nothing -> (Nothing, 0)
j@Just{} -> (j, 1)
instance Parseable () where
parse _ = (Just (), 0)
instance
( Parseable a
, Parseable b)
=> Parseable (a, b) where
parse = toPair . parse2Tuple
instance
( Parseable a
, Parseable b
, Parseable c)
=> Parseable (a,b,c) where
parse = toPair . parse3Tuple
toPair :: (a, b, c) -> (a, b)
toPair (a, b, _) = (a, b)
parse2Tuple
:: (Parseable a, Parseable b)
=> [String]
-> (Maybe (a, b), Int, [String])
parse2Tuple ss = let
(ma, na) = parse ss
sa = drop na ss
in case ma of
Nothing -> (Nothing, na, sa)
Just a -> let
(mb, nb) = parse sa
sb = drop nb sa
mTup = fmap (\b -> (a, b)) mb
in (mTup, na + nb, sb)
parse3Tuple
:: (Parseable a, Parseable b, Parseable c)
=> [String]
-> (Maybe (a, b, c), Int, [String])
parse3Tuple ss = case parse2Tuple ss of
(mt, nt, st) -> case mt of
Nothing -> (Nothing, nt, st)
Just (a, b) -> let
(mc, nc) = parse st
sc = drop nc st
mTup = fmap (\c -> (a, b, c)) mc
in (mTup, nt + nc, sc)