{-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE DefaultSignatures , FlexibleContexts , PolyKinds , TypeOperators #-} {-| Module : Graphics.QML.DataModel.Internal.Generic.Mock Copyright : (c) Marcin Mrotek, 2015 License : BSD3 Maintainer : marcin.jan.mrotek@gmail.com Stability : experimental -} module Graphics.QML.DataModel.Internal.Generic.Mock where import GHC.Generics {-| A class that constructs a mock object, with all fields set to 'undefined', for use with generic implementations that don't actually use the supplied data. Only data types with a single constuctor can have an unambiguous mock object. -} class Mock t where -- |Construct a mock object of a data type with a single constructor, with 'undefined' fields. mock :: t default mock :: (Generic t, GMock (Rep t)) => t mock = to gMock class GMock f where -- |Generic version of 'mock'. gMock :: f a instance GMock (K1 i c) where gMock = K1 undefined instance GMock f => GMock (M1 i t f) where gMock = M1 gMock instance (GMock a, GMock b) => GMock (a :*: b) where gMock = gMock :*: gMock