{-# LANGUAGE
BangPatterns
, DeriveFoldable
, DeriveFunctor
, DeriveTraversable
, GeneralizedNewtypeDeriving
, MultiParamTypeClasses
, OverloadedStrings
#-}
module Ditto.Types (
FormId(..)
, FormRange(..)
, encodeFormId
, formIdentifier
, Value(..)
, View(..)
, Proved(..)
, Result(..)
) where
import Control.Applicative (Alternative(..))
import Data.List.NonEmpty (NonEmpty(..))
import Data.String (IsString(..))
import Data.Text (Text)
import Torsor
import qualified Data.Text as T
data FormId
= FormId
{-# UNPACK #-} !Text
{-# UNPACK #-} !(NonEmpty Int)
| FormIdName
{-# UNPACK #-} !Text
{-# UNPACK #-} !Int
deriving (Eq, Ord, Show)
instance IsString FormId where
fromString x = FormIdName (T.pack x) 0
encodeFormId :: FormId -> Text
encodeFormId (FormId p xs) =
p <> "-val-" <> (T.intercalate "." $ foldr (\a as -> T.pack (show a) : as) [] xs)
encodeFormId (FormIdName x _) = x
formIdentifier :: FormId -> Int
formIdentifier (FormId _ (x :| _)) = x
formIdentifier (FormIdName _ x) = x
instance Torsor FormId Int where
add i (FormId p (x :| xs)) = FormId p $ (x + i) :| xs
add i (FormIdName n x) = FormIdName n $ x + i
difference a b = formIdentifier a - formIdentifier b
data FormRange
= FormRange FormId FormId
deriving (Eq, Show)
newtype View err v = View { unView :: [(FormRange, err)] -> v }
deriving (Semigroup, Monoid, Functor)
data Value a
= Default
| Missing
| Found a
deriving (Eq, Show, Functor, Traversable, Foldable)
instance Applicative Value where
pure = Found
(Found f) <*> (Found x) = Found (f x)
Default <*> _ = Default
Missing <*> _ = Missing
Found{} <*> Default = Default
Found{} <*> Missing = Default
instance Alternative Value where
empty = Missing
x@Found{} <|> _ = x
Default <|> _ = Default
Missing <|> x = x
instance Semigroup a => Semigroup (Value a) where
Missing <> Missing = Missing
Default <> Missing = Default
Missing <> Default = Default
Default <> Default = Default
Found x <> Found y = Found (x <> y)
Found x <> _ = Found x
_ <> Found y = Found y
data Result e ok
= Error [(FormRange, e)]
| Ok ok
deriving (Show, Eq, Functor, Foldable, Traversable)
instance Monad (Result e) where
return = Ok
Error x >>= _ = Error x
Ok x >>= f = f x
instance Applicative (Result e) where
pure = Ok
Error x <*> Error y = Error $ x ++ y
Error x <*> Ok _ = Error x
Ok _ <*> Error y = Error y
Ok x <*> Ok y = Ok $ x y
data Proved a = Proved
{ pos :: FormRange
, unProved :: a
} deriving (Show, Functor, Foldable, Traversable)