
"Trees that grows"
this (type families), or Tagged
http://hackage.haskell.org/package/tagged-0.8.5/docs/Data-Tagged.html
data Checked = Checked
Tagged Checked a
On 6 July 2017 at 16:09, Sylvain Henry
Hi,
You can use something similar to "Trees that grows" in GHC:
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-}
module Main where
import Data.Maybe
data Checked = Checked deriving (Show) data Unchecked = Unchecked deriving (Show)
type family F a b :: * where F Unchecked b = Maybe b F Checked b = b
-- data types are decorated with a phantom type indicating if they have been checked -- in which case "Maybe X" are replaced with "X" (see F above) data A c = A { a1 :: F c (B c) }
data B c = B { b1 :: F c (C c) }
data C c = C { c1 :: F c Int }
deriving instance Show (F c (B c)) => Show (A c) deriving instance Show (F c (C c)) => Show (B c) deriving instance Show (F c Int) => Show (C c)
class Checkable a where check :: a Unchecked -> a Checked
instance Checkable A where check (A mb) = A (check (fromJust mb))
instance Checkable B where check (B mc) = B (check (fromJust mc))
instance Checkable C where check (C mi) = C (fromJust mi)
main :: IO () main = do let a :: A Unchecked a = A (Just (B (Just (C (Just 10)))))
a' :: A Checked a' = check a print a print a'
$> ./Test A {a1 = Just (B {b1 = Just (C {c1 = Just 10})})} A {a1 = B {b1 = C {c1 = 10}}}
Cheers, Sylvain
On 06/07/2017 10:12, Baa wrote:
Hello Dear List!
Consider, I retrieve from external source some data. Internally it's represented as some complex type with `Maybe` fields, even more, some of fields are record types and have `Maybe` fields too. They are Maybe's because some information in this data can be missing (user error or it not very valuable and can be skipped):
data A = A { a1 :: Maybe B ... } data B = B { b1 :: Maybe C ... }
I retrieve it from network, files, i.e. external world, then I validate it, report errors of some missing fields, fix another one (which can be fixed, for example, replace Nothing with `Just default_value` or even I can fix `Just wrong` to `Just right`, etc, etc). After all of this, I know that I have "clean" data, so all my complex types now have `Just right_value` fields. But I need to process them as optional, with possible Nothing case! To avoid it I must create copies of `A`, `B`, etc, where `a1`, `b1` will be `B`, `C`, not `Maybe B`, `Maybe C`. Sure, it's not a case.
After processing and filtering, I create, for example, some resulting objects:
data Result { a :: A -- not Maybe! ... }
And even more: `a::A` in `Result` (I know it, after filtering) will not contain Nothings, only `Just right_values`s.
But each function which consumes `A` must do something with possible Nothing values even after filtering and fixing of `A`s.
I have, for example, function:
createResults :: [A] -> [Result] createResults alst = ... case of (a1 theA) -> Just right_value -> ... Nothing -> logError undefined -- can not happen
Fun here is: that it happens (I found bug in my filtering code with this `undefined`). But now I thought about it: what is the idiomatic way to solve such situation? When you need to have:
- COMPLEX type WITH Maybes - the same type WITHOUT Maybes
Alternative is to keep this Maybes to the very end of processing, what I don't like. Or to have types copies, which is more terrible, sure.
PS. I threw IOs away to show only the crux of the problem.
--- Cheers, Paul _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners